DBA Data[Home] [Help]

PACKAGE BODY: APPS.HRI_OLTP_PMV_DYNSQLGEN

Source


1 PACKAGE BODY hri_oltp_pmv_dynsqlgen AS
2 /* $Header: hriopsql.pkb 120.5 2006/02/02 06:11:17 cbridge noship $ */
3 
4 g_debug               VARCHAR2(5) := 'FALSE';
5 
6 g_temp_no_rollup      VARCHAR2(30) := NULL;
7 g_temp_no_value       VARCHAR2(30) := hri_oltp_view_message.get_unassigned_msg;
8 g_all_msg             VARCHAR2(30) := hri_oltp_view_message.get_all_msg;
9 
10 /* Hierarchy Column Metadata */
11 g_suph                VARCHAR2(30) := 'HRI_CS_SUPH';
12 g_suph_id             VARCHAR2(30) := 'PERSON_ID';
13 g_suph_level_col      VARCHAR2(30) := 'RELATIVE_LEVEL';
14 g_orgh                VARCHAR2(30) := 'HRI_CS_ORGH';
15 g_orgh_id             VARCHAR2(30) := 'ORGANIZATION_ID';
16 g_orgh_level_col      VARCHAR2(30) := 'ORG_RELATIVE_LEVEL';
17 g_posh                VARCHAR2(30) := 'HRI_CS_POSH';
18 g_posh_id             VARCHAR2(30) := 'POSITION_ID';
19 g_posh_level_col      VARCHAR2(30) := 'RELATIVE_LEVEL';
20 
21 /* Hierarchy Column Naming Standards */
22 g_sub_prefix          VARCHAR2(30) := 'SUB_';
23 g_subro_prefix        VARCHAR2(30) := 'SUBRO_';
24 g_view_suffix         VARCHAR2(30) := '_V';
25 g_crrnt_view_suffix   VARCHAR2(30) := '_X_V';
26 g_rollup_suffix       VARCHAR2(30) := 'RO';
27 
28 /* Default Start and End Dates */
29 g_start_of_time       DATE := hr_general.start_of_time;
30 g_end_of_time         DATE := hr_general.end_of_time;
31 
32 /* New Line */
33 g_rtn                 VARCHAR2(30) := '
34 ';
35 
36 TYPE g_sort_record_type IS RECORD
37      (column_name     VARCHAR2(60),
38       sort_direction  VARCHAR2(30));
39 
40 TYPE g_measure_type IS RECORD
41      (column_name     VARCHAR2(60),
42       aggregation     VARCHAR2(30));
43 
44 TYPE g_sort_record_tabtype IS TABLE OF g_sort_record_type
45            INDEX BY BINARY_INTEGER;
46 
47 TYPE g_measure_tabtype IS TABLE OF g_measure_type
48            INDEX BY BINARY_INTEGER;
49 
50 /******************************************************************************/
51 /* Given the dimension level code this function returns the dimension level   */
52 /* view. The dimension level code is in the format DIMENSION+DIMENSION_LEVEL  */
53 /******************************************************************************/
54 FUNCTION get_level_view_name(p_dim_level_code   IN VARCHAR2)
55                RETURN VARCHAR2 IS
56 
57 /* Cursor returning the dimension level view for a given level */
58   CURSOR viewby_view_csr(v_lvl_short_name   IN VARCHAR2) IS
59   SELECT level_values_view_name   view_name
60   FROM bisbv_dimension_levels  lvl
61   WHERE lvl.dimension_level_short_name = v_lvl_short_name;
62 
63   l_view_name   VARCHAR2(30);
64 
65 BEGIN
66 
67 /* Open the cursor with the DIMENSION_LEVEL part of the input code */
68   OPEN viewby_view_csr(SUBSTR(p_dim_level_code,INSTR(p_dim_level_code,'+')+1));
69   FETCH viewby_view_csr INTO l_view_name;
70   CLOSE viewby_view_csr;
71 
72   RETURN l_view_name;
73 
74 EXCEPTION WHEN OTHERS THEN
75   CLOSE viewby_view_csr;
76   RAISE;
77 END get_level_view_name;
78 
79 /******************************************************************************/
80 /* Get (hard coded) hierarchy details                                         */
81 /******************************************************************************/
82 PROCEDURE get_hierarchy_details(p_ak_level_code          IN VARCHAR2,
83                                 p_hierarchy_view         OUT NOCOPY VARCHAR2,
84                                 p_hierarchy_view_suffix  OUT NOCOPY VARCHAR2,
85                                 p_hierarchy_level        OUT NOCOPY VARCHAR2,
86                                 p_hierarchy_col          OUT NOCOPY VARCHAR2) IS
87 
88 BEGIN
89 
90 /* Find out which hierarchy view and join column to use */
91   IF (p_ak_level_code = 'HRI_ORGANIZATION+HISTORIC') THEN
92     p_hierarchy_view := g_orgh;
93     p_hierarchy_view_suffix := g_view_suffix;
94     p_hierarchy_level  := g_orgh_level_col;
95     p_hierarchy_col  := g_orgh_id;
96   ELSIF (p_ak_level_code = 'HRI_POSITION+HISTORIC') THEN
97     p_hierarchy_view := g_posh;
98     p_hierarchy_view_suffix := g_view_suffix;
99     p_hierarchy_level  := g_posh_level_col;
100     p_hierarchy_col  := g_posh_id;
101   ELSIF (p_ak_level_code = 'HRI_SUPERVISOR+HISTORIC') THEN
102     p_hierarchy_view := g_suph;
103     p_hierarchy_view_suffix := g_view_suffix;
104     p_hierarchy_level  := g_suph_level_col;
105     p_hierarchy_col  := g_suph_id;
106   ELSIF (p_ak_level_code = 'HRI_SUPERVISOR+CURRENT') THEN
107     p_hierarchy_view := g_suph;
108     p_hierarchy_view_suffix := g_crrnt_view_suffix;
109     p_hierarchy_level  := g_suph_level_col;
110     p_hierarchy_col  := g_suph_id;
111   END IF;
112 
113 END get_hierarchy_details;
114 
115 /******************************************************************************/
116 /* Get (hard coded) details if the viewby is a hierarchy                      */
117 /******************************************************************************/
118 PROCEDURE get_viewby_hierarchy_details( p_viewby_level_code     IN VARCHAR2,
119                                         p_hierarchy_col         IN VARCHAR2,
120                                         p_hierarchy_level       IN VARCHAR2,
121                                         p_hierarchy_join        IN OUT NOCOPY VARCHAR2,
122                                         p_hierarchy_view_suffix IN OUT NOCOPY VARCHAR2,
123                                         p_viewby_select         IN OUT NOCOPY VARCHAR2,
124                                         p_viewby_col            IN OUT NOCOPY VARCHAR2,
125                                         p_hierarchy_condition   OUT NOCOPY VARCHAR2,
126                                         p_order_by_clause       OUT NOCOPY VARCHAR2,
127                                         p_group_by_clause       OUT NOCOPY VARCHAR2) IS
128 
129 BEGIN
130 
131 /* Finish the hierarchy join ('AND fact.column = hrchy.') */
132 /* Get the viewby column and doctor the viewby display column in the select */
133 /* clause if the top node is selected. Also doctor the column order to make */
134 /* the top node appear first if selected. Apply the relevant conditions to */
135 /* the hierarchy view to include top, enable rollup or include subordinates */
136   IF (p_viewby_level_code = 'HRI_VIEWBY_ORGH+HRI_DRCTS_ROLLUP_INC' OR
137       p_viewby_level_code = 'HRI_VIEWBY_SUPH+HRI_DRCTS_ROLLUP_INC') THEN
138     p_hierarchy_join := p_hierarchy_join || g_subro_prefix || p_hierarchy_col;
139     p_viewby_col := 'hrchy.' || g_sub_prefix || p_hierarchy_col;
140     p_viewby_select :=
141      '  DECODE(hrchy.' || g_sub_prefix || p_hierarchy_level || ',' || g_rtn ||
142      '           0, viewby.value || ''' || g_temp_no_rollup || ''',' || g_rtn ||
143      '         viewby.value)           VIEWBY';
144     p_hierarchy_condition :=
145      'AND (hrchy.' || g_sub_prefix || p_hierarchy_level || ' = 1' || g_rtn ||
146      ' OR (hrchy.' || g_sub_prefix || p_hierarchy_level || ' = 0' ||
147      ' AND hrchy.' || g_subro_prefix || g_sub_prefix || p_hierarchy_level
148        || ' = 0))' || g_rtn;
149     p_order_by_clause :=
150      '  DECODE(hrchy.' || g_sub_prefix || p_hierarchy_level ||
151      ',0,1,2)';
152     p_group_by_clause :=
153      ' ,DECODE(hrchy.' || g_sub_prefix || p_hierarchy_level ||
154      ',0,1,2)' || g_rtn ||
155      ' ,DECODE(hrchy.' || g_sub_prefix || p_hierarchy_level || ',' || g_rtn ||
156      '           0, viewby.value || ''' || g_temp_no_rollup || ''',' || g_rtn ||
157      '         viewby.value)' || g_rtn;
158     p_hierarchy_view_suffix := g_rollup_suffix || p_hierarchy_view_suffix;
159   ELSIF (p_viewby_level_code = 'HRI_VIEWBY_ORGH+HRI_DRCTS_ROLLUP' OR
160          p_viewby_level_code = 'HRI_VIEWBY_SUPH+HRI_DRCTS_ROLLUP') THEN
161     p_hierarchy_join := p_hierarchy_join || g_subro_prefix || p_hierarchy_col;
162     p_viewby_col := 'hrchy.' || g_sub_prefix ||p_hierarchy_col;
163     p_hierarchy_condition := 'AND hrchy.' || g_sub_prefix || p_hierarchy_level
164                           || ' = 1' || g_rtn;
165     p_hierarchy_view_suffix := g_rollup_suffix || p_hierarchy_view_suffix;
166   ELSIF (p_viewby_level_code = 'HRI_VIEWBY_ORGH+HRI_ALL_INC' OR
167          p_viewby_level_code = 'HRI_VIEWBY_SUPH+HRI_ALL_INC') THEN
168     p_hierarchy_join := p_hierarchy_join || g_sub_prefix || p_hierarchy_col;
169     p_viewby_col := 'hrchy.' || g_sub_prefix || p_hierarchy_col;
170   ELSIF (p_viewby_level_code = 'HRI_VIEWBY_ORGH+HRI_ALL' OR
171          p_viewby_level_code = 'HRI_VIEWBY_SUPH+HRI_ALL') THEN
172     p_hierarchy_join := p_hierarchy_join || g_sub_prefix || p_hierarchy_col;
173     p_viewby_col := 'hrchy.' || g_sub_prefix || p_hierarchy_col;
174     p_hierarchy_condition := 'AND hrchy.' || g_sub_prefix || p_hierarchy_level
175                           || ' > 0' || g_rtn;
176   END IF;
177 
178 END get_viewby_hierarchy_details;
179 
180 /******************************************************************************/
181 /* This is the procedure which builds up the main SQL statement. It queries   */
182 /* the parameter table of values passed into the package, and gets all the    */
183 /* information in the AK Region for the report. It combines this information  */
184 /* to form the SQL query.                                                     */
185 /*                                                                            */
186 /* Some special cases are also handled by this procedure. The most basic PMV  */
187 /* reports can be handled generically without referring to specific objects.  */
188 /* However reports using the time dimension need special treatment. Also in   */
189 /* the "special" category are hierarchical parameters not yet supported.      */
190 /******************************************************************************/
191 FUNCTION build_sql_stmt(p_region_code      IN VARCHAR2,
192                         p_params_tbl       IN BIS_PMV_PAGE_PARAMETER_TBL)
193                  RETURN VARCHAR2 IS
194 
195 /* Loop counter */
196   l_counter                   NUMBER;  -- used to go through sort record table
197 
198 /* Information about ORDERBY parameter */
199   l_orderby_column            VARCHAR2(1000);   -- column name passed in for sort
200 
201 /* Information about VIEWBY object */
202   l_viewby_view               VARCHAR2(30);   -- view name of viewby view
203   l_viewby_level              VARCHAR2(60);   -- viewby DIMENSION+LEVEL name
204   l_viewby_col                VARCHAR2(30);   -- fact column joins to viewby id
205   l_viewby_select             VARCHAR2(2000); -- doctored viewby display column
206 
207 /* Information about TIME object */
208   l_time_view                 VARCHAR2(60);  -- view name of time view
209   l_time_level                VARCHAR2(60);  -- time DIMENSION+LEVEL name
210   l_time_col                  VARCHAR2(60);  -- fact column joins to time level
211   l_time_from_date            DATE;          -- time from period start date
212   l_time_to_date              DATE;          -- time to period end date
213   l_report_start_date         DATE;          -- report date - period type
214   l_report_date               DATE;          -- report date to
215   l_viewby_time_condition     VARCHAR2(500); -- time condition on time view
216   l_no_viewby_time_condition  VARCHAR2(500); -- time condition on fact view
217 
218 /* Information about hierarchy object */
219   l_hierarchy_view            VARCHAR2(60);  -- view name of hierarchy object
220   l_hierarchy_view_suffix     VARCHAR2(60);  -- "_X_V" current "_V" historic
221   l_hierarchy_col             VARCHAR2(60);  -- fact column joins to hierarchy
222   l_hierarchy_level           VARCHAR2(30);  -- hierarchy DIMENSION+LEVEL name
223   l_hierarchy_join            VARCHAR2(500); -- hierarchy - fact join condition
224   l_hierarchy_condition       VARCHAR2(500); -- include top node condition
225   l_hierarchy_order_by        VARCHAR2(500); -- orders by top node first
226 
227 /* AK Base Object */
228   l_db_object_name            VARCHAR2(30);  -- Database object from AK Object
229 
230 /* Variables for SQL query */
231   l_sql_query                 VARCHAR2(4000); -- holds SQL to return
232   l_params_header             VARCHAR2(2000); -- debug output header
233   l_select_clause             VARCHAR2(2000); -- main SELECT
234   l_from_clause               VARCHAR2(2000); -- main FROM
235   l_where_clause              VARCHAR2(2000); -- main WHERE
236   l_group_by_clause           VARCHAR2(2000); -- main GROUP BY
237   l_order_by_clause           VARCHAR2(2000); -- main ORDER BY
238   l_outer_select              VARCHAR2(2000); -- allows default time periods
239   l_union_select              VARCHAR2(2000); -- allows default time periods
240   l_union_clause              VARCHAR2(2000); -- allows default time periods
241   l_sort_record_tab           g_sort_record_tabtype; -- allows alternative sort
242   l_measure_tab               g_measure_tabtype; -- stores measures
243   l_calc_measure              VARCHAR2(2000); -- builds up calculated measures
244 
245 /* Cursor returning all AK Region Items for a given region */
246   CURSOR ak_region_info_csr IS
247   SELECT
248    itm.attribute1                   column_type
249   ,itm.attribute2                   level_code
250   ,lower(itm.attribute3)            column_name
251   ,itm.attribute_code               item_code
252   ,itm.attribute9                   aggregation
253   ,itm.node_display_flag            display_flag
254   ,itm.attribute15                  lov_table
255   ,itm.attribute4                   lov_where_clause
256   ,itm.attribute11                  hrchy_view_override
257   ,itm.order_sequence               order_sequence
258   ,itm.order_direction              order_direction
259   ,lower(reg.database_object_name)  object_name
260   ,reg.attribute11                  region_where_clause
261   ,itm.display_sequence             display_sequence
262   FROM
263    ak_region_items  itm
264   ,ak_regions       reg
265   WHERE reg.region_code = p_region_code
266   AND reg.region_application_id = 453
267   AND itm.region_code = reg.region_code
268   AND reg.region_application_id = itm.region_application_id
269 /* Must have hidden parameters first so that hierarchy can be extracted */
270 /* before other parts of the sql statement are built up. */
271 /* Calculated measures must be returned after view column measures */
272 /* which is done by the 3rd column
273 /* Also depending on HRI_PERIOD_TYPE dimension being extracted before */
274 /* HRI_REPORT_DATE which is done by the last order by column */
275   ORDER BY DECODE(itm.attribute1,
276                     'HIDE PARAMETER', 1,
277                     'HIDE VIEW BY DIMENSION', 2,
278                   3)
279   ,DECODE(SUBSTR(itm.attribute_code,1,12),
280              'HRI_P_HIERAR',1,
281              'HRI_P_VIEWBY',2,
282            3)
283   ,DECODE(SUBSTR(itm.attribute3,1,1),'"',2,1)
284   ,itm.attribute2;
285 
286 BEGIN
287 
288 /******************************************************************************/
289 /* LOCAL VARIABLE INITIALIZATION */
290 /*********************************/
291 
292 /* Default the viewby select column so that if */
293 /* the value is null a "no value" label is displayed */
294   l_viewby_select :=
295             '  DECODE(viewby.id, ' || g_rtn ||
296             '           ''-1'', ''' || g_temp_no_value || ''',' || g_rtn ||
297             '           ''NA_EDW'',''' || g_temp_no_value || ''',' || g_rtn ||
298             '         viewby.value)          VIEWBY';
299 
300 /* Build a SQL header with debug information - all parameters passed in */
301 /* Initialize the header */
302   l_params_header := '-- AK REGION: ' || p_region_code || g_rtn ||
303                      '-- Parameter Name:   Parameter Value' || g_rtn;
304 
305 
306 /******************************************************************************/
307 /* PARAMETER TABLE LOOP 1 - GET VIEWBY/TIME PARAMETERS */
308 /*******************************************************/
309 
310 /* Loop through parameters to get the parameter special cases */
311   FOR i IN p_params_tbl.first..p_params_tbl.last LOOP
312   /* Bug  4633221 - Translation problem with 'All' */
313   IF (p_params_tbl(i).parameter_value = g_all_msg) THEN
314   /* Add parameter information to debug header */
315     l_params_header := l_params_header || '-- ' ||
316                        p_params_tbl(i).parameter_name  || ':  ' ||
317                        'All' || g_rtn;
318   ELSE
319   /* Add parameter information to debug header */
320     l_params_header := l_params_header || '-- ' ||
321                        p_params_tbl(i).parameter_name  || ':  ' ||
322                        p_params_tbl(i).parameter_value || g_rtn;
323   END IF;
324 
325   /* Retrieve information parameter special cases */
326   /* Pull out information about the VIEWBY dimension */
327     IF (p_params_tbl(i).parameter_name = 'VIEW_BY') THEN
328     /* Get the viewby view from the dimension metadata (may be null) */
329       l_viewby_view := get_level_view_name(p_params_tbl(i).parameter_value);
330     /* Record the viewby DIMENSION+LEVEL name */
331       l_viewby_level  := p_params_tbl(i).parameter_value;
332 
333   /* Pull out information about the ORDERBY object */
334     ELSIF (p_params_tbl(i).parameter_name = 'ORDERBY') THEN
335       l_orderby_column := LTRIM(p_params_tbl(i).parameter_value);
336 
337   /* Pull out information about the TIME dimension */
338     ELSIF (substr(p_params_tbl(i).parameter_name,1,4) = 'TIME') THEN
339       IF substr(p_params_tbl(i).parameter_name,-5,5)='_FROM' THEN
340       /* Get the start date */
341         l_time_from_date     := p_params_tbl(i).period_date;
342       /* Add the condition for the start date */
343         l_viewby_time_condition := l_viewby_time_condition ||
344             'AND tim.start_date >= to_date(''' ||
345              to_char(l_time_from_date,'DD-MM-YYYY') ||
346             ''',''DD-MM-YYYY'')' || g_rtn;
347       ELSIF substr(p_params_tbl(i).parameter_name,-3,3)='_TO' THEN
348       /* Get the end date */
349         l_time_to_date       := p_params_tbl(i).period_date;
350       /* Add the condition for the end date */
351         l_viewby_time_condition := l_viewby_time_condition ||
352             'AND tim.end_date   <= to_date(''' ||
353              to_char(l_time_to_date,'DD-MM-YYYY') ||
354             ''',''DD-MM-YYYY'')' || g_rtn;
355       END IF;
356 
357   /* Pull out information about the TIME dimension level */
358     ELSIF (p_params_tbl(i).parameter_name = 'PERIOD_TYPE') THEN
359       l_time_view   := get_level_view_name(p_params_tbl(i).parameter_value);
363     ELSIF (p_params_tbl(i).parameter_name = 'HRI_NO_JOIN_DATE+HRI_REPORT_DATE') THEN
360       l_time_level  := 'TIME+' || p_params_tbl(i).parameter_value;
361 
362   /* Pull out information about the HRI REPORT DATE dimension */
364       l_report_date := p_params_tbl(i).period_date;
365 
366   /* Pull out information about the HRI PERIOD TYPE dimension */
367     ELSIF (p_params_tbl(i).parameter_name = 'HRI_NO_JOIN_PERIOD+HRI_PERIOD_TYPE') THEN
368     /* Set the report start date as l_report_date - l_period type */
369       IF (p_params_tbl(i).parameter_id = '''Y''') THEN
370         l_report_start_date := add_months(l_report_date, -12);
371       ELSIF (p_params_tbl(i).parameter_id = '''Q''') THEN
372         l_report_start_date := add_months(l_report_date, -3);
373       ELSIF (p_params_tbl(i).parameter_id = '''CM''') THEN
374         l_report_start_date := add_months(l_report_date, -1);
375       END IF;
376     END IF;
377 
378   END LOOP;
379 
380 
381 /******************************************************************************/
382 /* AK Region Loop - Builds up SQL Statement */
383 /********************************************/
384 
385 /* Get AK Region Items Information */
386   FOR measure_rec IN ak_region_info_csr LOOP
387 
388   /* The base view name - same on every cursor row */
389     IF (l_db_object_name IS NULL) THEN
390       l_db_object_name := measure_rec.object_name;
391     /* 115.1 - add the region where clause only if there is one defined */
392       IF (measure_rec.region_where_clause IS NOT NULL) THEN
393         l_where_clause := l_where_clause || measure_rec.region_where_clause || g_rtn;
394       END IF;
395     END IF;
396 
397   /***************/
398   /* AK MEASURES */
399   /***************/
400     IF (measure_rec.column_type = 'MEASURE' OR
401         measure_rec.column_type IS NULL) THEN
402     /* Ignore measures which are calculated AK Region Items */
403       IF (SUBSTR(measure_rec.column_name,1,1) <> '"' AND
404           measure_rec.aggregation IS NOT NULL) THEN
405       /* Store information about the measure */
406         l_measure_tab(measure_rec.display_sequence).column_name :=
407                                                  measure_rec.column_name;
408         l_measure_tab(measure_rec.display_sequence).aggregation :=
409                                                  measure_rec.aggregation;
410       /* Check for non-default sort order */
411         IF (measure_rec.order_sequence IS NOT NULL) THEN
412           l_sort_record_tab(measure_rec.order_sequence).column_name :=
413                                                  measure_rec.item_code;
414           l_sort_record_tab(measure_rec.order_sequence).sort_direction :=
415                                                  measure_rec.order_direction;
416         END IF;
417         IF (measure_rec.display_flag = 'Y') THEN
418         /* SELECT CLAUSE BUILD - add all non AK calculated measure columns */
419           l_select_clause := l_select_clause || g_rtn ||
420           ' ,' || measure_rec.aggregation || '(fact.' || measure_rec.column_name
421                || ')     "' || measure_rec.item_code || '"';
422           l_union_select := l_union_select || g_rtn || ' ,0';
423           l_outer_select := l_outer_select || g_rtn || ' ,SUM(' ||
424                       measure_rec.item_code || ')   ' || measure_rec.item_code;
425         END IF;
426 
427 /* Bug 2670163 - If the order by is a calculated measure, substitute the */
428 /* calculation for the order by column */
429       ELSIF (measure_rec.item_code = SUBSTR(l_orderby_column,1,
430                                             INSTR(l_orderby_column,' ')-1)) THEN
431       /* Else if a displayed calculated measure */
432         l_calc_measure := measure_rec.column_name;
433       /* Put quotes around any character which could possibly appear */
434       /* next to a column name in the calculated measure string */
435         l_calc_measure := REPLACE(l_calc_measure,'(','"("');
436         l_calc_measure := REPLACE(l_calc_measure,')','")"');
437         l_calc_measure := REPLACE(l_calc_measure,'+','"+"');
438         l_calc_measure := REPLACE(l_calc_measure,'-','"-"');
439         l_calc_measure := REPLACE(l_calc_measure,'/','"/"');
440         l_calc_measure := REPLACE(l_calc_measure,'*','"*"');
441       /* Loop through the single column measures and swap in the column */
442       /* names and aggregation */
443         l_counter := l_measure_tab.first;
444         WHILE (l_counter IS NOT NULL) LOOP
445           l_calc_measure := REPLACE(l_calc_measure,
446                       '"' || l_measure_tab(l_counter).column_name||'"',
447                       l_measure_tab(l_counter).aggregation ||
448                       '(fact.'||l_measure_tab(l_counter).column_name||')');
449           l_counter := l_measure_tab.next(l_counter);
450         END LOOP;
451      /* Remove any excess quotes */
452         l_calc_measure := REPLACE(l_calc_measure,'"');
453      /* Set the order by column to the calculated measure */
454         l_orderby_column := l_calc_measure ||
455                           SUBSTR(l_orderby_column,INSTR(l_orderby_column,' '));
456       END IF;
457 
458   /****************************************************************/
459   /* AK DIMENSIONS - Hierarchy Item / Report Date / Time / Viewby */
460   /****************************************************************/
461     ELSE
465       /* Get (hard coded) hierarchy details */
462     /* HRI_P_HIERARCHY item will crop up first as the cursor */
463     /* is ordered to return HIDE PARAMETER items first */
464       IF (measure_rec.item_code = 'HRI_P_HIERARCHY') THEN
466         get_hierarchy_details
467           (p_ak_level_code => measure_rec.level_code,
468            p_hierarchy_view => l_hierarchy_view,
469            p_hierarchy_view_suffix => l_hierarchy_view_suffix,
470            p_hierarchy_level => l_hierarchy_level,
471            p_hierarchy_col => l_hierarchy_col);
472       /* Start building up the hierarchy join using the fact column */
473         l_hierarchy_join := 'AND fact.' || measure_rec.column_name || ' = hrchy.';
474 
475     /* HRI_REPORT_DATE will crop up next as the cursor is ordered */
476     /* to return HIDE VIEWBY PARAMETER items second */
477       ELSIF (measure_rec.item_code = 'HRI_P_REPORTING_DATE') THEN
478         IF (INSTR(measure_rec.column_name,'.') > 0) THEN
479           l_time_col := measure_rec.column_name;
480         ELSE
481           l_time_col := 'fact.' || measure_rec.column_name;
482         END IF;
483 
484     /* Time Dimension */
485       ELSIF (l_time_level = measure_rec.level_code) THEN
486         l_time_col := measure_rec.column_name;
487         IF (measure_rec.column_type = 'HIDE VIEW BY DIMENSION') THEN
488           l_no_viewby_time_condition :=
489             'AND fact.' || l_time_col ||
490             ' BETWEEN  to_date(''' ||
491              to_char(NVL(l_time_from_date,g_start_of_time),'DD-MM-YYYY') ||
492               ''',''DD-MM-YYYY'')' || g_rtn ||
493             '      AND to_date(''' ||
494              to_char(NVL(l_time_to_date,g_end_of_time),'DD-MM-YYYY') ||
495               ''',''DD-MM-YYYY'')' || g_rtn;
496         END IF;
497       END IF; -- AK Dimension Split Out
498 
499     /* Viewby Dimension */
500       IF (l_viewby_level = measure_rec.level_code) THEN
501       /* If an LOV Table has been specified, override the viewby view */
502         l_viewby_view := NVL(measure_rec.lov_table, l_viewby_view);
503       /* Get the fact column to join to the viewby view */
504         l_viewby_col := measure_rec.column_name;
505       /* Check the viewby special cases - HIERARCHYs */
506         IF (SUBSTR(l_viewby_level,1,10) = 'HRI_VIEWBY') THEN
507           get_viewby_hierarchy_details
508              (p_viewby_level_code => l_viewby_level,
509               p_hierarchy_col => l_hierarchy_col,
510               p_hierarchy_level => l_hierarchy_level,
511               p_hierarchy_join => l_hierarchy_join,
512               p_hierarchy_view_suffix => l_hierarchy_view_suffix,
513               p_viewby_col => l_viewby_col,
514               p_viewby_select => l_viewby_select,
515               p_hierarchy_condition => l_hierarchy_condition,
516               p_order_by_clause => l_order_by_clause,
517               p_group_by_clause => l_group_by_clause);
518         ELSE
519         /* l_hierarchy_join is already of the form 'AND fact.column = hrchy.' */
520           l_hierarchy_join := l_hierarchy_join || g_sub_prefix || l_hierarchy_col;
521         END IF;
522 
523       END IF;  -- Viewby Dimension
524 
525     /*******************************************************/
526     /* PARAMETER TABLE LOOP 2 - Match Dimension Parameters */
527     /*******************************************************/
528       FOR i IN p_params_tbl.first..p_params_tbl.last LOOP
529       /* If the parameter is a dimension level with values selected */
530       /* then add it to the WHERE clause */
531         IF (p_params_tbl(i).parameter_name = measure_rec.level_code AND
532             p_params_tbl(i).parameter_value <> 'All' AND
533      /* Bug  4633221 - Translation problem with 'All' */
534 	    p_params_tbl(i).parameter_value <> g_all_msg AND
535             p_params_tbl(i).parameter_value IS NOT NULL AND
536             SUBSTR(p_params_tbl(i).parameter_name,1,11) <> 'HRI_NO_JOIN') THEN
537          /* WHERE CLAUSE BUILD - Simple Dimension Parameter Value */
538           IF (INSTR(measure_rec.column_name,'.') > 0) THEN
539             l_where_clause := l_where_clause ||
540                    'AND ' || measure_rec.column_name ||
541                    ' IN (&' || p_params_tbl(i).parameter_name || ')' || g_rtn;
542           ELSE
543             l_where_clause := l_where_clause ||
544                    'AND fact.' || measure_rec.column_name ||
545                    ' IN (&' || p_params_tbl(i).parameter_name || ')' || g_rtn;
546           END IF;
547         END IF;
548 
549       END LOOP; -- Parameter Table
550 
551     END IF; -- AK Measure or Dimension
552 
553   END LOOP; -- AK Region Items
554 
555 /******************************************************************************/
556 /* BUILD UP SQL STATEMENT */
557 /**************************/
558 
559 /* The SELECT clause always picks a VIEWBY column and the list of measure */
563                        l_select_clause                   || g_rtn;
560 /* columns already built up */
561   l_select_clause :=  'SELECT'                           || g_rtn ||
562                        l_viewby_select                   ||
564 
565 /* The FROM clause always picks the database object from the AK region and */
566 /* the list of values view for the VIEWBY level */
567   l_from_clause :=    'FROM' || g_rtn ||
568                       '  '   || l_db_object_name || '   fact'   || g_rtn ||
569                       ' ,'   || l_viewby_view    || '   viewby' || g_rtn ||
570                        l_from_clause;
571 
572 /* The WHERE clause always has the VIEWBY join condition and any */
573 /* conditions already built up from the parameter values */
574   IF (INSTR(l_viewby_col,'.') > 0) THEN
575     l_where_clause :=   'WHERE viewby.id = ' || l_viewby_col || g_rtn ||
576                          l_where_clause;
577   ELSE
578     l_where_clause :=   'WHERE viewby.id = fact.' || l_viewby_col || g_rtn ||
579                          l_where_clause;
580   END IF;
581 
582 /* Add reporting date condition to where clause if relevant */
583   IF (l_report_start_date IS NOT NULL) THEN
584     l_where_clause := l_where_clause ||
585                       'AND ' || l_time_col ||
586                       ' BETWEEN to_date(''' || to_char(l_report_start_date,'DD-MM-YYYY') ||
587                       ''',''DD-MM-YYYY'') AND to_date(''' || to_char(l_report_date,'DD-MM-YYYY') ||
588                       ''',''DD-MM-YYYY'')' || g_rtn;
589   END IF;
590 
591 /* The VIEWBY value and id columns are always in the GROUP BY clause */
592   l_group_by_clause := 'GROUP BY' || g_rtn ||
593                        '  DECODE(viewby.id, ' || g_rtn ||
594                        '           ''-1'', ''' || g_temp_no_value || ''',' || g_rtn ||
595                        '           ''NA_EDW'',''' || g_temp_no_value || ''',' || g_rtn ||
596                        '         viewby.value)' || g_rtn ||
597                        ' ,viewby.value' || g_rtn ||
598                        ' ,viewby.id' || g_rtn ||
599                        l_group_by_clause;
600 
601 /* Unless the VIEWBY is time, the order by clause is: */
602   l_counter := l_sort_record_tab.first;
603 /* If there is no sort order passed in parameters */
604   IF (l_orderby_column IS NULL) THEN
605 
606   /* If there is a sort order defined on the region */
607     IF (l_counter IS NOT NULL) THEN
608     /* Populate order by clause with the stored sort columns */
609       WHILE (l_counter IS NOT NULL) LOOP
610         IF (l_order_by_clause IS NULL) THEN
611           l_order_by_clause := l_sort_record_tab(l_counter).column_name ||
612                                ' ' || l_sort_record_tab(l_counter).sort_direction;
613         ELSE
614           l_order_by_clause := l_order_by_clause || g_rtn ||
615                                ' ,' || l_sort_record_tab(l_counter).column_name ||
616                                ' ' || l_sort_record_tab(l_counter).sort_direction;
617         END IF;
618         l_counter := l_sort_record_tab.next(l_counter);
619       END LOOP;
620       l_order_by_clause := 'ORDER BY' || g_rtn || l_order_by_clause;
621     ELSE -- No sort order defined on region
622       IF (l_order_by_clause IS NULL) THEN
623         l_order_by_clause := 'ORDER BY viewby.value';
624       ELSE
625         l_order_by_clause := 'ORDER BY ' || l_order_by_clause || g_rtn ||
626                              ' ,viewby.value';
627       END IF;
628     END IF;
629 
630   ELSE -- Sort order passed in parameter table
631 
632     IF (l_order_by_clause IS NOT NULL) THEN
633       l_order_by_clause := 'ORDER BY ' || l_order_by_clause || g_rtn ||
634                            ' ,' || l_orderby_column || g_rtn ||
635                            ' ,viewby.value';
636     ELSE
637       l_order_by_clause := 'ORDER BY ' || l_orderby_column || g_rtn ||
638                            ' ,viewby.value';
639     END IF;
640 
641   END IF;
642 
643 /* Alter above clauses depending on parameters selected */
644 /* If the query is restricted by the time parameter, and the TIME level is */
645 /* different to the VIEWBY level */
646   IF (l_time_level IS NOT NULL AND
647       l_time_level <> l_viewby_level AND
648      (l_time_from_date IS NOT NULL OR l_time_to_date IS NOT NULL)) THEN
649 
650     IF (l_no_viewby_time_condition IS NOT NULL) THEN
651       l_where_clause :=  l_where_clause || l_no_viewby_time_condition;
652     ELSE
653     /* Add the TIME view to the FROM clause */
654       l_from_clause :=   l_from_clause ||
655                         ' ,' || l_time_view      || '   tim' || g_rtn;
656     /* Add the TIME-FACT join and TIME condition to the WHERE clause */
657       l_where_clause :=  l_where_clause ||
658                         'AND tim.id = fact.'   || l_time_col || g_rtn ||
659                          l_viewby_time_condition;
660     END IF;
661 
662   END IF;
663 
664 /* If the VIEWBY level is a time dimension level */
665   IF (SUBSTR(l_viewby_level,1,5) = 'TIME+' AND
666       l_time_from_date IS NOT NULL AND
667       l_time_to_date IS NOT NULL) THEN
668 
669   /* Create an outer SELECT statement so that the query results can be */
670   /* combined with a set of default values for every time period - this */
671   /* enables trend reporting */
672     l_outer_select := 'SELECT' || g_rtn ||
673                       ' VIEWBY         VIEWBY' ||
677   /* Add the ORDERBY attribute to the SELECT clause to order the results */
674                        l_outer_select || g_rtn ||
675                       'FROM (' || g_rtn;
676 
678   /* by time period start date */
679     l_select_clause :=  l_select_clause ||
680                        ' ,viewby.start_date     ORDERBY' || g_rtn;
681 
682   /* If the TIME and VIEWBY levels are the same */
683     IF (l_viewby_level = l_time_level) THEN
684     /* Add the TIME condition to the WHERE clause changing it to refer to */
685     /* the VIEWBY view instead of the TIME view */
686       l_where_clause := l_where_clause ||
687                       REPLACE(l_viewby_time_condition,'tim','viewby');
688     END IF;
689 
690   /* Add the ORDERBY attribute to the GROUP BY clause */
691     l_group_by_clause := l_group_by_clause || ' ,viewby.start_date' || g_rtn;
692 
693   /* Construct a UNION ALL clause containing all the available time periods */
694     l_union_clause := 'UNION ALL'      || g_rtn ||
695                       'SELECT' || g_rtn ||
696                       '  viewby.value          VIEWBY'  ||
697                        l_union_select  || g_rtn ||
698                       ' ,viewby.start_date     ORDERBY' || g_rtn ||
699                       'FROM'           || g_rtn ||
700                       '  ' || l_viewby_view || '   viewby' || g_rtn ||
701                       'WHERE 1=1' || g_rtn ||
702                        REPLACE(l_viewby_time_condition,'tim','viewby') ||
703                       ')' || g_rtn ||
704                       'GROUP BY VIEWBY, ORDERBY' || g_rtn;
705   /* Move the ORDER BY clause to the outer SELECT statement */
706     l_order_by_clause := 'ORDER BY ORDERBY';
707   ELSE
708 
709   /* Remove the outer select statement */
710     l_outer_select := NULL;
711 
712   END IF;
713 
714 /* If the hierarchy parameter is populated */
715   IF (l_hierarchy_view IS NOT NULL) THEN
716 
717   /* Add the hierarchy view to the FROM clause */
718     l_from_clause := l_from_clause ||
719                    ' ,' || l_hierarchy_view || l_hierarchy_view_suffix || '   hrchy' || g_rtn;
720 
721   /* Add the hierarchy join and condition to the WHERE clause */
722     l_where_clause := l_where_clause || l_hierarchy_join || g_rtn ||
723                       l_hierarchy_condition;
724 
725   END IF;
726 
727 /* Build query from components */
728   l_sql_query := l_outer_select    ||
729                  l_select_clause   ||
730                  l_from_clause     ||
731                  l_where_clause    ||
732                  l_group_by_clause ||
733                  l_union_clause    ||
734                  l_order_by_clause;
735 
736 /* Return the query */
737   RETURN --l_params_header ||
738            l_sql_query;
739 
740 EXCEPTION
741  WHEN OTHERS THEN
742   IF (ak_region_info_csr%ISOPEN) THEN
743     CLOSE ak_region_info_csr;
744   END IF;
745   RETURN l_params_header ||
746          '-- ' || SQLERRM || g_rtn ||
747          '-- ' || SQLCODE;
748 END build_sql_stmt;
749 
750 
751 /******************************************************************************/
752 /* This is the procedure which builds up the main SQL statement for no viewby */
753 /* reports. It is very similar to the build_sql_stmt function                 */
754 /******************************************************************************/
755 FUNCTION build_no_viewby_sql_stmt(p_region_code      IN VARCHAR2,
756                                   p_params_tbl       IN BIS_PMV_PAGE_PARAMETER_TBL)
757                  RETURN VARCHAR2 IS
758 
759 /* AK Base Object */
760   l_db_object_name        VARCHAR2(30);
761 
762 /* Variables for SQL query */
763   l_sql_query             VARCHAR2(4000);
764   l_params_header         VARCHAR2(2000);
765   l_select_clause         VARCHAR2(2000);
766   l_from_clause           VARCHAR2(2000);
767   l_where_clause          VARCHAR2(2000);
768   l_order_by_clause       VARCHAR2(2000);
769 
770 /* Sort order variables */
771   l_sort_record_tab       g_sort_record_tabtype;
772   l_counter               NUMBER;
773 
774 /* Cursor returning all AK Region Items for a given region */
775   CURSOR ak_region_info_csr IS
776   SELECT
777    itm.attribute1                   column_type
778   ,itm.attribute2                   level_code
779   ,lower(itm.attribute3)            column_name
780   ,itm.attribute_code               item_code
781   ,itm.attribute9                   aggregation
782   ,itm.node_display_flag            display_flag
783   ,itm.attribute15                  lov_table
784   ,itm.attribute4                   lov_where_clause
785   ,itm.attribute11                  hrchy_view_override
786   ,itm.order_sequence               order_sequence
787   ,itm.order_direction              order_direction
788   ,lower(reg.database_object_name)  object_name
789   FROM
790    ak_region_items  itm
791   ,ak_regions       reg
792   WHERE reg.region_code = p_region_code
793   AND reg.region_application_id = 453
794   AND itm.region_code = reg.region_code
795   AND reg.region_application_id = itm.region_application_id
796   ORDER BY itm.display_sequence;
797 
798 BEGIN
799 
800 /* Build a SQL header with debug information - all parameters passed in */
801 /* Initialize the header */
805   FOR i IN p_params_tbl.first..p_params_tbl.last LOOP
802   l_params_header := '-- Parameter Name:   Parameter Value' || g_rtn;
803 
804 /* Loop through parameters to get the parameter special cases */
806   /* Bug 4633221 */
807   IF (p_params_tbl(i).parameter_value = g_all_msg) THEN
808   /* Add parameter information to debug header */
809     l_params_header := l_params_header || '-- ' ||
810                        p_params_tbl(i).parameter_name  || ':  ' ||
811                        'All' || g_rtn;
812   ELSE
813       l_params_header := l_params_header || '-- ' ||
814                        p_params_tbl(i).parameter_name  || ':  ' ||
815                        p_params_tbl(i).parameter_value || g_rtn;
816   END IF;
817 
818   END LOOP;
819 
820 /* Get AK Region Items Information */
821   FOR measure_rec IN ak_region_info_csr LOOP
822 
823   /* The base view name - same on every cursor row */
824     l_db_object_name := measure_rec.object_name;
825 
826   /* Build up the select clauses containing all measure columns */
827     IF (l_select_clause IS NULL) THEN
828       l_select_clause := ' ( fact.' || measure_rec.column_name || ' )   ' || measure_rec.item_code;
829     ELSE
830       l_select_clause := l_select_clause || g_rtn ||
831          ' ,( fact.' || measure_rec.column_name || ' )   ' || measure_rec.item_code;
832     END IF;
833 
834     /* Check for non-default sort order */
835      IF (measure_rec.order_sequence IS NOT NULL) THEN
836        l_sort_record_tab(measure_rec.order_sequence).column_name := measure_rec.item_code;
837        l_sort_record_tab(measure_rec.order_sequence).sort_direction := measure_rec.order_direction;
838      END IF;
839 
840   END LOOP;
841 
842   l_from_clause := 'FROM ' || l_db_object_name || '  fact';
843 
844 /* The order by clause is: */
845   l_counter := l_sort_record_tab.first;
846   IF (l_counter IS NOT NULL) THEN
847     WHILE (l_counter IS NOT NULL) LOOP
848       IF (l_order_by_clause IS NULL) THEN
849         l_order_by_clause := 'ORDER BY ' || l_sort_record_tab(l_counter).column_name ||
850                              ' ' || l_sort_record_tab(l_counter).sort_direction;
851       ELSE
852         l_order_by_clause := 'ORDER BY ' || l_order_by_clause || g_rtn ||
853                              ' ,' || l_sort_record_tab(l_counter).column_name ||
854                              ' ' || l_sort_record_tab(l_counter).sort_direction;
855       END IF;
856       l_counter := l_sort_record_tab.next(l_counter);
857     END LOOP;
858   ELSE
859     l_order_by_clause := 'ORDER BY 1';
860   END IF;
861 
862 /* Build query from components */
863   l_sql_query := 'SELECT' || g_rtn ||
864                   l_select_clause || g_rtn ||
865                   l_from_clause || g_rtn ||
866                  'WHERE 1=1' || g_rtn ||
867                   l_order_by_clause;
868 
869 /* Return the query */
870   RETURN --l_params_header ||
871          l_sql_query;
872 
873 EXCEPTION
874  WHEN OTHERS THEN
875   IF (ak_region_info_csr%ISOPEN) THEN
876     CLOSE ak_region_info_csr;
877   END IF;
878   RETURN l_params_header ||
879          '-- ' || SQLERRM || g_rtn ||
880          '-- ' || SQLCODE;
881 END build_no_viewby_sql_stmt;
882 
883 
884 /******************************************************************************/
885 /* This is the procedure which builds up the main SQL statement for a drill   */
886 /* into report. A parameter table of values is passed into the function, and  */
887 /* it gets all the information in the AK Region for the report. It combines   */
888 /* this information to form the SQL query.                                    */
889 /*                                                                            */
890 /* Some special cases are also handled by this procedure. The most basic PMV  */
891 /* reports can be handled generically without referring to specific objects.  */
892 /* However reports using the time dimension need special treatment. Also in   */
893 /* the "special" category are hierarchical parameters not yet supported.      */
894 /******************************************************************************/
895 FUNCTION build_drill_into_sql_stmt(p_params_tbl IN BIS_PMV_PAGE_PARAMETER_TBL
896                                   ,p_ak_region_code   IN VARCHAR2)
897                  RETURN VARCHAR2 IS
898 
899 /* Loop counter */
900   l_counter                   NUMBER;  -- used to go through sort record table
901 
902 /* Dummy Variable */
903   l_dummy                     VARCHAR2(100);  -- Dummy passed into functions
904 
905 /* Information about HRI_VIEWBY parameter */
906   l_actl_drll_frm_vwby        VARCHAR2(60);   -- HRI_VIEWBY level passed in
907   l_effct_drll_frm_vwby       VARCHAR2(60);   -- Effective HRI_VIEWBY level
908   l_hri_viewby_id             VARCHAR2(60);   -- Parameter_id of viewby
909 
910 /* Information about ORDERBY parameter */
911   l_orderby_column            VARCHAR2(1000);   -- column passed in to order by
912 
913 /* Information about VIEWBY object */
914   l_viewby_view               VARCHAR2(30);   -- view name of viewby view
915   l_viewby_level              VARCHAR2(60);   -- viewby DIMENSION+LEVEL name
916   l_viewby_col                VARCHAR2(30);   -- fact column joins to viewby id
917   l_viewby_select             VARCHAR2(2000); -- doctored viewby display column
918 
919 /* Information about TIME object */
923   l_time_from_date            DATE;          -- time from period start date
920   l_time_view                 VARCHAR2(60);  -- view name of time view
921   l_time_level                VARCHAR2(60);  -- time DIMENSION+LEVEL name
922   l_time_col                  VARCHAR2(60);  -- fact column joins to time level
924   l_time_to_date              DATE;          -- time to period end date
925   l_report_start_date         DATE;          -- report date - period type
926   l_report_date               DATE;          -- report date to
927   l_time_condition            VARCHAR2(500); -- time condition on fact view
928 
929 /* Information about hierarchy object */
930   l_hierarchy_view            VARCHAR2(60);  -- view name of hierarchy object
931   l_hierarchy_view_suffix     VARCHAR2(60);  -- "_X_V" current "_V" historic
932   l_hierarchy_col             VARCHAR2(60);  -- fact column joins to hierarchy
933   l_hierarchy_level           VARCHAR2(30);  -- hierarchy DIMENSION+LEVEL name
934   l_hierarchy_join            VARCHAR2(500); -- hierarchy - fact join condition
935   l_hierarchy_condition       VARCHAR2(500); -- include top node condition
936   l_hierarchy_order_by        VARCHAR2(500); -- orders by top node first
937   l_fact_col_hrchy            VARCHAR2(30);  -- fact column joining to hierarchy
938 
939 /* AK Base Objects */
940   l_db_object_name            VARCHAR2(30);  -- Database object from AK Object
941 
942 /* Variables for SQL query */
943   l_sql_query                 VARCHAR2(4000); -- holds SQL to return
944   l_params_header             VARCHAR2(2000); -- debug output header
945   l_select_clause             VARCHAR2(2000); -- main SELECT
946   l_from_clause               VARCHAR2(2000); -- main FROM
947   l_where_clause              VARCHAR2(2000); -- main WHERE
948   l_order_by_clause           VARCHAR2(2000); -- main ORDER BY
949   l_sort_record_tab           g_sort_record_tabtype; -- allows alternative sort
950 
951 /* Cursor returning all AK Region Items for a given region */
952   CURSOR ak_region_info_csr IS
953   SELECT
954    reg.region_code                  region_code
955   ,itm.attribute1                   column_type
956   ,itm.attribute2                   level_code
957   ,lower(itm.attribute3)            column_name
958   ,itm.attribute_code               item_code
959   ,itm.attribute9                   aggregation
960   ,itm.node_display_flag            display_flag
961   ,itm.attribute15                  lov_table
962   ,itm.attribute4                   lov_where_clause
963   ,itm.attribute11                  hrchy_view_override
964   ,itm.order_sequence               order_sequence
965   ,itm.order_direction              order_direction
966   ,itm.attribute14                  column_datatype
967   ,lower(reg.database_object_name)  object_name
968   ,reg.attribute11                  region_where_clause
969   ,itm.display_sequence             display_sequence
970   FROM
971    ak_region_items  itm
972   ,ak_regions       reg
973   WHERE reg.region_code = p_ak_region_code
974   AND reg.region_application_id = 453
975   AND itm.region_code = reg.region_code
976   AND reg.region_application_id = itm.region_application_id
977 /* Must have hidden parameters first so that hierarchy can be extracted */
978 /* before other parts of the sql statement are built up. Also depending */
979 /* on HRI_PERIOD_TYPE dimension being extracted before HRI_REPORT_DATE */
980 /* which is done by the second order by column */
981 /* Must have hidden parameters first so that hierarchy can be extracted */
982 /* before other parts of the sql statement are built up. */
983 /* Calculated measures must be returned after view column measures */
984 /* which is done by the 3rd column
985 /* Also depending on HRI_PERIOD_TYPE dimension being extracted before */
986 /* HRI_REPORT_DATE which is done by the last order by column */
987   ORDER BY DECODE(itm.attribute1,
988                     'HIDE PARAMETER', 1,
989                     'HIDE VIEW BY DIMENSION', 2,
990                   3)
991   ,DECODE(SUBSTR(itm.attribute_code,1,12),
992              'HRI_P_HIERAR',1,
993              'HRI_P_VIEWBY',2,
994            3)
995   ,DECODE(SUBSTR(itm.attribute3,1,1),'"',2,1)
996   ,itm.display_sequence;
997   -- cbridge removed for bug 3919506 -- ,itm.attribute2;
998 
999 BEGIN
1000 
1001 /******************************************************************************/
1002 /* LOCAL VARIABLE INITIALIZATION */
1003 /*********************************/
1004 
1005 /* Initialize the HRI_VIEWBY level variables */
1006   l_actl_drll_frm_vwby  := 'NONE';
1007   l_effct_drll_frm_vwby := 'NONE';
1008 
1009 /* Default the viewby select column so that if */
1010 /* the value is null a "no value" label is displayed */
1011   l_viewby_select :=
1012             '  DECODE(viewby.id, ' || g_rtn ||
1013             '           ''-1'', ''' || g_temp_no_value || ''',' || g_rtn ||
1014             '           ''NA_EDW'',''' || g_temp_no_value || ''',' || g_rtn ||
1015             '         viewby.value)          VIEWBY';
1016 
1017 /* Build a SQL header with debug information - all parameters passed in */
1018 /* Initialize the header */
1019   l_params_header := '-- AK REGION: ' || p_ak_region_code || g_rtn ||
1020                      '-- Parameter Name:   Parameter Value' || g_rtn;
1021 
1022 
1023 /******************************************************************************/
1024 /* PARAMETER TABLE LOOP 1 - GET VIEWBY/TIME PARAMETERS */
1025 /*******************************************************/
1026 
1027 /* Loop through parameters to get the parameter special cases */
1031   /* Add parameter information to debug header */
1028   FOR i IN p_params_tbl.first..p_params_tbl.last LOOP
1029   /*Bug 4633221 */
1030   IF (p_params_tbl(i).parameter_value = g_all_msg) THEN
1032     l_params_header := l_params_header || '-- ' ||
1033                        p_params_tbl(i).parameter_name  || ':  ' ||
1034                        'All' || g_rtn;
1035   ELSE
1036     l_params_header := l_params_header || '-- ' ||
1037                        p_params_tbl(i).parameter_name  || ':  ' ||
1038                        p_params_tbl(i).parameter_value || g_rtn;
1039   END IF;
1040 
1041   /* Retrieve information parameter special cases */
1042   /* Pull out information about the VIEWBY dimension */
1043     IF (p_params_tbl(i).parameter_name = 'VIEW_BY') THEN
1044     /* Get the viewby view from the dimension metadata (may be null) */
1045       l_viewby_view := get_level_view_name(p_params_tbl(i).parameter_value);
1046     /* Record the viewby DIMENSION+LEVEL name */
1047       l_viewby_level  := p_params_tbl(i).parameter_value;
1048 
1049   /* Pull out information about the ORDERBY object */
1050     ELSIF (p_params_tbl(i).parameter_name = 'ORDERBY') THEN
1051       l_orderby_column := p_params_tbl(i).parameter_value;
1052 
1053   /* Pull out information about the TIME dimension */
1054     ELSIF (substr(p_params_tbl(i).parameter_name,1,4) = 'TIME') THEN
1055       IF substr(p_params_tbl(i).parameter_name,-5,5)='_FROM' THEN
1056       /* Get the start date */
1057         l_time_from_date     := p_params_tbl(i).period_date;
1058       ELSIF substr(p_params_tbl(i).parameter_name,-3,3)='_TO' THEN
1059       /* Get the end date */
1060         l_time_to_date       := p_params_tbl(i).period_date;
1061       END IF;
1062 
1063   /* Pull out information about the TIME dimension level */
1064     ELSIF (p_params_tbl(i).parameter_name = 'PERIOD_TYPE') THEN
1065       l_time_level  := 'TIME+' || p_params_tbl(i).parameter_value;
1066 
1067   /* Pull out information about the HRI REPORT DATE dimension */
1068     ELSIF (p_params_tbl(i).parameter_name = 'HRI_NO_JOIN_DATE+HRI_REPORT_DATE') THEN
1069       l_report_date := p_params_tbl(i).period_date;
1070 
1071   /* Pull out information about the HRI PERIOD TYPE dimension */
1072     ELSIF (p_params_tbl(i).parameter_name =
1073                    'HRI_NO_JOIN_PERIOD+HRI_PERIOD_TYPE') THEN
1074     /* Set the report start date as l_report_date - l_period type */
1075       IF (p_params_tbl(i).parameter_id = '''Y''') THEN
1076         l_report_start_date := add_months(l_report_date, -12);
1077       ELSIF (p_params_tbl(i).parameter_id = '''Q''') THEN
1078         l_report_start_date := add_months(l_report_date, -3);
1079       ELSIF (p_params_tbl(i).parameter_id = '''CM''') THEN
1080         l_report_start_date := add_months(l_report_date, -1);
1081       END IF;
1082   /* Pull out information about the Hierarchy Viewby */
1083     ELSIF (substr(p_params_tbl(i).parameter_name,1,10) = 'HRI_VIEWBY'
1084            AND p_params_tbl(i).parameter_id IS NOT NULL) -- bug 4566643
1085          THEN
1086       l_actl_drll_frm_vwby  := p_params_tbl(i).parameter_name;
1087       l_effct_drll_frm_vwby := p_params_tbl(i).parameter_name;
1088       l_hri_viewby_id := p_params_tbl(i).parameter_id;
1089   /* Get the indicator corresponding to the column drilled from */
1090     ELSIF (p_params_tbl(i).parameter_name =  'HRI_INDICATOR_COL') THEN
1091       l_where_clause := 'AND fact.' || p_params_tbl(i).parameter_value ||
1092                         ' = 1' || g_rtn;
1093     END IF;
1094 
1095   END LOOP;
1096 
1097 
1098 /******************************************************************************/
1099 /* AK Region Loop - Builds up SQL Statement */
1100 /********************************************/
1101 
1102 /* Get AK Region Items Information */
1103   FOR measure_rec IN ak_region_info_csr LOOP
1104 
1105   /******************/
1106   /* Current Region */
1107   /******************/
1108   /* The base view name - same on every cursor row */
1109     IF (l_db_object_name IS NULL) THEN
1110       l_db_object_name := measure_rec.object_name;
1111     /* 115.1 - add the region where clause only if there is one defined */
1112       IF (measure_rec.region_where_clause IS NOT NULL) THEN
1113         l_where_clause := l_where_clause ||
1114                           measure_rec.region_where_clause || g_rtn;
1115       END IF;
1116     END IF;
1117 
1118   /* Display columns - Measures */
1119     IF (measure_rec.column_type = 'MEASURE' OR
1120         measure_rec.column_type IS NULL) THEN
1121     /* Ignore measures which are calculated AK Region Items */
1122       IF (SUBSTR(measure_rec.column_name,1,1) <> '"') THEN
1123       /* Check for non-default sort order */
1124         IF (measure_rec.order_sequence IS NOT NULL) THEN
1125           l_sort_record_tab(measure_rec.order_sequence).column_name :=
1126                measure_rec.item_code;
1127           l_sort_record_tab(measure_rec.order_sequence).sort_direction :=
1128                measure_rec.order_direction;
1129         END IF;
1130       /* SELECT CLAUSE BUILD - add all non AK calculated measure columns */
1131         IF (measure_rec.column_datatype = 'C') THEN
1132           l_select_clause := l_select_clause || g_rtn ||
1133              ' ,' || measure_rec.aggregation || '(fact.' ||
1134              measure_rec.column_name || ')     ' || measure_rec.item_code;
1135         ELSE
1136           l_select_clause := l_select_clause || g_rtn ||
1137              ' ,' || measure_rec.aggregation || '( to_char(fact.' ||
1138              measure_rec.column_name || '))     ' || measure_rec.item_code;
1139         END IF;
1143     ELSE
1140       END IF;
1141 
1142   /* Hierarchy Item / Report Date / Time / Viewby / Dimension */
1144     /* HRI_P_HIERARCHY item will crop up first as the cursor */
1145     /* is ordered to return HIDE PARAMETER items first */
1146       IF (measure_rec.item_code = 'HRI_P_HIERARCHY') THEN
1147       /* Store fact column which joins to hierarchy */
1148         l_fact_col_hrchy := measure_rec.column_name;
1149         IF (l_actl_drll_frm_vwby <> 'HRI_VIEWBY_ORGH+HRI_ALL_INC' AND
1150             l_actl_drll_frm_vwby <> 'HRI_VIEWBY_SUPH+HRI_ALL_INC') THEN
1151         /* Get (hard coded) hierarchy details */
1152           get_hierarchy_details
1153             (p_ak_level_code => measure_rec.level_code,
1154              p_hierarchy_view => l_hierarchy_view,
1155              p_hierarchy_view_suffix => l_hierarchy_view_suffix,
1156              p_hierarchy_level => l_hierarchy_level,
1157              p_hierarchy_col => l_hierarchy_col);
1158         /* Start building up the hierarchy join using the fact column */
1159           l_hierarchy_join := 'AND fact.' || measure_rec.column_name ||
1160                               ' = hrchy.' || g_sub_prefix || l_hierarchy_col;
1161         END IF;
1162     /* Time Dimension */
1163       ELSIF (l_time_level = measure_rec.level_code) THEN
1164         IF (l_time_from_date IS NOT NULL) THEN
1165           l_time_condition := l_time_condition ||
1166         'AND fact.' || measure_rec.column_name || ' >= to_date(''' ||
1167         to_char(l_time_from_date,'DD-MM-YYYY') || ''',''DD-MM-YYYY'')' || g_rtn;
1168         END IF;
1169         IF (l_time_to_date IS NOT NULL) THEN
1170           l_time_condition := l_time_condition ||
1171           'AND fact.' || measure_rec.column_name || ' <= to_date(''' ||
1172           to_char(l_time_to_date,'DD-MM-YYYY') || ''',''DD-MM-YYYY'')' || g_rtn;
1173         END IF;
1174      /* Viewby Dimension */
1175       ELSIF (l_viewby_level = measure_rec.level_code) THEN
1176       /* If an LOV Table has been specified, override the viewby view */
1177         l_viewby_view := NVL(measure_rec.lov_table, l_viewby_view);
1178       /* Get the fact column to join to the viewby view */
1179         l_viewby_col := measure_rec.column_name;
1180       /* Check the viewby special cases - HIERARCHYs */
1181         IF (SUBSTR(l_viewby_level,1,10) = 'HRI_VIEWBY') THEN
1182           get_viewby_hierarchy_details
1183              (p_viewby_level_code => l_viewby_level,
1184               p_hierarchy_col => l_hierarchy_col,
1185               p_hierarchy_level => l_hierarchy_level,
1186               p_hierarchy_join => l_hierarchy_join,
1187               p_hierarchy_view_suffix => l_hierarchy_view_suffix,
1188               p_viewby_col => l_viewby_col,
1189               p_viewby_select => l_viewby_select,
1190               p_hierarchy_condition => l_hierarchy_condition,
1191               p_order_by_clause => l_order_by_clause,
1192               p_group_by_clause => l_dummy);
1193         END IF;
1194 
1195       ELSE -- Other Dimension (Not HRI_P_HIERARCHY, TIME or VIEWBY parameter)
1196 
1197       /*******************************************************/
1198       /* PARAMETER TABLE LOOP 2 - Match Dimension Parameters */
1199       /*******************************************************/
1200         FOR i IN p_params_tbl.first..p_params_tbl.last LOOP
1201         /* If the parameter is a dimension level with values selected */
1202         /* then add it to the WHERE clause */
1203           IF (p_params_tbl(i).parameter_name = measure_rec.level_code AND
1204               p_params_tbl(i).parameter_value <> 'All' AND
1205         /* Bug 4633221 */
1206               p_params_tbl(i).parameter_value <> g_all_msg AND
1207               p_params_tbl(i).parameter_value IS NOT NULL AND
1208               measure_rec.column_name IS NOT NULL AND
1209               SUBSTR(p_params_tbl(i).parameter_name,1,11) <> 'HRI_NO_JOIN') THEN
1210           /* WHERE CLAUSE BUILD - Simple Dimension Parameter Value */
1211           /* Bug 2702283 - Put hierarchy related conditions in l_hierarchy_condition */
1212             IF (INSTR(measure_rec.column_name,'.') > 0) THEN
1213             /* If the drill is from the top level directs rollup */
1214               IF ((l_actl_drll_frm_vwby = 'HRI_VIEWBY_ORGH+HRI_DRCTS_ROLLUP_INC' OR
1215                    l_actl_drll_frm_vwby = 'HRI_VIEWBY_SUPH+HRI_DRCTS_ROLLUP_INC') AND
1216                    p_params_tbl(i).parameter_id = l_hri_viewby_id) THEN
1217               /* Switch the effective mode to "No Rollup Include Subs" */
1218                 l_effct_drll_frm_vwby := SUBSTR(l_actl_drll_frm_vwby,1,16) || 'HRI_ALL_INC';
1219               /* Dump the hierarchy */
1220                 l_hierarchy_view := NULL;
1221               END IF;
1222               IF (l_effct_drll_frm_vwby = 'HRI_VIEWBY_ORGH+HRI_ALL_INC' AND
1223                   SUBSTR(p_params_tbl(i).parameter_name,1,12) = 'ORGANIZATION')
1224               THEN
1225                 IF (l_hierarchy_view IS NULL) THEN
1226                   l_where_clause := l_where_clause ||
1227                    'AND fact.' || l_fact_col_hrchy ||
1228                    ' IN (&' || l_actl_drll_frm_vwby || ')' || g_rtn;
1229                 ELSE
1230                   l_where_clause := l_where_clause ||
1231                          'AND ' || measure_rec.column_name ||
1232                          ' IN (&' || l_actl_drll_frm_vwby || ')' || g_rtn;
1233                 END IF;
1234               ELSIF (l_effct_drll_frm_vwby = 'HRI_VIEWBY_ORGH+HRI_DRCTS_ROLLUP_INC' AND
1235                   SUBSTR(p_params_tbl(i).parameter_name,1,12) = 'ORGANIZATION')
1236               THEN
1237                 l_hierarchy_condition := l_hierarchy_condition ||
1241                   SUBSTR(p_params_tbl(i).parameter_name,1,10) = 'HRI_PERSON')
1238                        'AND ' || measure_rec.column_name ||
1239                        ' IN (&' || l_actl_drll_frm_vwby || ')' || g_rtn;
1240               ELSIF (l_effct_drll_frm_vwby = 'HRI_VIEWBY_SUPH+HRI_ALL_INC' AND
1242               THEN
1243                 IF (l_hierarchy_view IS NULL) THEN
1244                   l_where_clause := l_where_clause ||
1245                    'AND fact.' || l_fact_col_hrchy ||
1246                    ' IN (&' || l_actl_drll_frm_vwby || ')' || g_rtn;
1247                 ELSE
1248                   l_where_clause := l_where_clause ||
1249                          'AND ' || measure_rec.column_name ||
1250                          ' IN (&' || l_actl_drll_frm_vwby || ')' || g_rtn;
1251                 END IF;
1252               ELSIF (l_effct_drll_frm_vwby = 'HRI_VIEWBY_SUPH+HRI_DRCTS_ROLLUP_INC' AND
1253                   SUBSTR(p_params_tbl(i).parameter_name,1,10) = 'HRI_PERSON')
1254               THEN
1255                 l_hierarchy_condition := l_hierarchy_condition ||
1256                        'AND ' || measure_rec.column_name ||
1257                        ' IN (&' || l_actl_drll_frm_vwby || ')' || g_rtn;
1258               ELSIF (l_effct_drll_frm_vwby <> 'HRI_VIEWBY_ORGH+HRI_ALL_INC' AND
1259                      l_effct_drll_frm_vwby <> 'HRI_VIEWBY_SUPH+HRI_ALL_INC') THEN
1260                 l_hierarchy_condition := l_hierarchy_condition ||
1261                    'AND ' || measure_rec.column_name ||
1262                   ' IN (&' || p_params_tbl(i).parameter_name || ')' || g_rtn;
1263               END IF;
1264             ELSE
1265               l_where_clause := l_where_clause ||
1266                      'AND fact.' || measure_rec.column_name ||
1267                      ' IN (&' || p_params_tbl(i).parameter_name || ')' || g_rtn;
1268             END IF;
1269 
1270           END IF;
1271 
1272         END LOOP; -- Parameter Table
1273 
1274       END IF;
1275 
1276     END IF; -- Current Region Measure or Dimension
1277 
1278   END LOOP; -- AK Region Items
1279 
1280 /******************************************************************************/
1281 /* BUILD UP SQL STATEMENT */
1282 /**************************/
1283 
1284 /* The SELECT clause always picks a VIEWBY column and the list of measure */
1285 /* columns already built up */
1286   l_select_clause :=  'SELECT'                           || g_rtn ||
1287                        l_viewby_select                   ||
1288                        l_select_clause                   || g_rtn;
1289 
1290 /* The FROM clause always picks the database object from the AK region and */
1291 /* the list of values view for the VIEWBY level */
1292   l_from_clause :=    'FROM' || g_rtn ||
1293                       '  '   || l_db_object_name || '   fact'   || g_rtn ||
1294                       ' ,'   || l_viewby_view    || '   viewby' || g_rtn ||
1295                        l_from_clause;
1296 
1297 /* The WHERE clause always has the VIEWBY join condition and any */
1298 /* conditions already built up from the parameter values */
1299   IF (INSTR(l_viewby_col,'.') > 0) THEN
1300     l_where_clause :=   'WHERE viewby.id = ' || l_viewby_col || g_rtn ||
1301                          l_where_clause;
1302   ELSE
1303     l_where_clause :=   'WHERE viewby.id = fact.' || l_viewby_col || g_rtn ||
1304                          l_where_clause;
1305   END IF;
1306 
1307 /* Add reporting date condition to where clause if relevant */
1308   IF (l_report_start_date IS NOT NULL) THEN
1309     l_where_clause := l_where_clause ||
1310       'AND ' || l_time_col ||
1311       ' BETWEEN to_date(''' || to_char(l_report_start_date,'DD-MM-YYYY') ||
1312       ''',''DD-MM-YYYY'') AND to_date(''' || to_char(l_report_date,'DD-MM-YYYY')
1313    || ''',''DD-MM-YYYY'')' || g_rtn;
1314   END IF;
1315 
1316 /* Unless the VIEWBY is time, the order by clause is: */
1317   l_counter := l_sort_record_tab.first;
1318 /* If there is no sort order passed in parameters */
1319   IF (l_orderby_column IS NULL) THEN
1320 
1321   /* If there is a sort order defined on the region */
1322     IF (l_counter IS NOT NULL) THEN
1323     /* Populate order by clause with the stored sort columns */
1324       WHILE (l_counter IS NOT NULL) LOOP
1325         IF (l_order_by_clause IS NULL) THEN
1326           l_order_by_clause := l_sort_record_tab(l_counter).column_name ||
1327                                ' ' || l_sort_record_tab(l_counter).sort_direction;
1328         ELSE
1329           l_order_by_clause := l_order_by_clause || g_rtn ||
1330                                ' ,' || l_sort_record_tab(l_counter).column_name ||
1331                                ' ' || l_sort_record_tab(l_counter).sort_direction;
1332         END IF;
1333         l_counter := l_sort_record_tab.next(l_counter);
1334       END LOOP;
1335       l_order_by_clause := 'ORDER BY' || g_rtn || l_order_by_clause;
1336     ELSE -- No sort order defined on region
1337       IF (l_order_by_clause IS NULL) THEN
1338         l_order_by_clause := 'ORDER BY viewby.value';
1339       ELSE
1340         l_order_by_clause := 'ORDER BY ' || l_order_by_clause || g_rtn ||
1341                              ' ,viewby.value';
1342       END IF;
1343     END IF;
1344 
1345   ELSE -- Sort order passed in parameter table
1346 
1347     IF (l_order_by_clause IS NOT NULL) THEN
1348       l_order_by_clause := 'ORDER BY ' || l_order_by_clause || g_rtn ||
1349                            ' ,' || l_orderby_column || g_rtn ||
1350                            ' ,viewby.value';
1351     ELSE
1352       l_order_by_clause := 'ORDER BY ' || l_orderby_column || g_rtn ||
1356   END IF;
1353                            ' ,viewby.value';
1354     END IF;
1355 
1357 
1358 /* Alter above clauses depending on parameters selected */
1359 /* If the query is restricted by the time parameter, and the TIME level is */
1360 /* different to the VIEWBY level */
1361   IF (l_time_condition IS NOT NULL) THEN
1362     l_where_clause :=  l_where_clause || l_time_condition;
1363   END IF;
1364 
1365 /* If the hierarchy parameter is populated */
1366   IF (l_hierarchy_view IS NOT NULL) THEN
1367 
1368   /* Add the hierarchy view to the FROM clause */
1369     l_from_clause := l_from_clause ||
1370                    ' ,' || l_hierarchy_view || l_hierarchy_view_suffix || '   hrchy' || g_rtn;
1371 
1372   /* Add the hierarchy join and condition to the WHERE clause */
1373     l_where_clause := l_where_clause || l_hierarchy_join || g_rtn ||
1374                       l_hierarchy_condition;
1375 
1376   END IF;
1377 
1378 /* Build query from components */
1379   l_sql_query := l_select_clause   ||
1380                  l_from_clause     ||
1381                  l_where_clause    ||
1382                  l_order_by_clause;
1383 
1384 /* Return the query */
1385   RETURN -- l_params_header ||
1386           l_sql_query;
1387 
1388 EXCEPTION
1389  WHEN OTHERS THEN
1390   IF (ak_region_info_csr%ISOPEN) THEN
1391     CLOSE ak_region_info_csr;
1392   END IF;
1393   RETURN l_params_header ||
1394          '-- ' || SQLERRM || g_rtn ||
1395          '-- ' || SQLCODE;
1396 END build_drill_into_sql_stmt;
1397 
1398 /******************************************************************************/
1399 /* Builds a SQL header to help identify the SQL start                         */
1400 /******************************************************************************/
1401 FUNCTION make_sql_header RETURN VARCHAR2 IS
1402 
1403   l_sql_header   VARCHAR2(500);
1404 
1405 BEGIN
1406 
1407   l_sql_header :=  '-- '                                      || g_rtn ||
1408                    '-- /****************************************/' || g_rtn ||
1409                    '-- /* Start of SQL Statement               */' || g_rtn ||
1410                    '-- /* Generated by HRI_OLTP_PMV_DYNSQLGEN  */' || g_rtn ||
1411                    '-- /***************************************/' || g_rtn ||
1412                    '-- ';
1413 
1414   RETURN l_sql_header;
1415 
1416 END make_sql_header;
1417 
1418 /******************************************************************************/
1419 /* Builds a SQL footer to help identify the SQL end                           */
1420 /******************************************************************************/
1421 FUNCTION make_sql_footer RETURN VARCHAR2 IS
1422 
1423   l_sql_footer   VARCHAR2(500);
1424 
1425 BEGIN
1426 
1427   l_sql_footer :=  '-- '                                || g_rtn ||
1428                    '-- /*****************************/' || g_rtn ||
1429                    '-- /* End of SQL Statement      */' || g_rtn ||
1430                    '-- /*****************************/' || g_rtn ||
1431                    '-- ';
1432 
1433   RETURN l_sql_footer;
1434 
1435 END make_sql_footer;
1436 
1437 
1438 /******************************************************************************/
1439 /*                  PUBLIC Procdures and Functions                            */
1440 /******************************************************************************/
1441 
1442 /******************************************************************************/
1443 /* Main function which inputs the parameters and the query AK Region and      */
1444 /* dynamically builds the SQL statement which forms the basis of the query.   */
1445 /******************************************************************************/
1446 FUNCTION get_query(p_params_tbl       IN BIS_PMV_PAGE_PARAMETER_TBL,
1447                    p_ak_region_code   IN VARCHAR2)
1448                   return varchar2 IS
1449 
1450   l_sql_text          VARCHAR2(4000);
1451   l_sql_header        VARCHAR2(500);
1452   l_sql_query         VARCHAR2(4000);
1453   l_sql_footer        VARCHAR2(500);
1454 
1455 BEGIN
1456 
1457   l_sql_query  := build_sql_stmt(p_ak_region_code, p_params_tbl);
1458   l_sql_header := make_sql_header;
1459   l_sql_footer := make_sql_footer;
1460   l_sql_text   := l_sql_header || g_rtn || l_sql_query || g_rtn || l_sql_footer;
1461 
1462   RETURN l_sql_text;
1463 
1464 EXCEPTION
1465 /* On error return the Error Message and Error Code */
1466  WHEN OTHERS THEN
1467    RETURN  '-- ' || SQLERRM || g_rtn ||
1468            '-- ' || SQLCODE;
1469 END get_query;
1470 
1471 /******************************************************************************/
1472 /* Main function which inputs the parameters and the query AK Region and      */
1473 /* dynamically builds the SQL statement which forms the basis of the query.   */
1474 /******************************************************************************/
1475 FUNCTION get_no_viewby_query(p_params_tbl       IN BIS_PMV_PAGE_PARAMETER_TBL,
1476                              p_ak_region_code   IN VARCHAR2)
1477                   return varchar2 IS
1478 
1479   l_sql_text          VARCHAR2(4000);
1480   l_sql_header        VARCHAR2(500);
1481   l_sql_query         VARCHAR2(4000);
1482   l_sql_footer        VARCHAR2(500);
1483 
1484 BEGIN
1485 
1486   l_sql_query  := build_no_viewby_sql_stmt(p_ak_region_code, p_params_tbl);
1487   l_sql_header := make_sql_header;
1488   l_sql_footer := make_sql_footer;
1489   l_sql_text   := l_sql_header || g_rtn || l_sql_query || g_rtn || l_sql_footer;
1490 
1491   RETURN l_sql_text;
1492 
1493 EXCEPTION
1494 /* On error return the Error Message and Error Code */
1495  WHEN OTHERS THEN
1496    RETURN  '-- ' || SQLERRM || g_rtn ||
1497            '-- ' || SQLCODE;
1498 END get_no_viewby_query;
1499 
1500 /******************************************************************************/
1501 /* Main function which inputs the parameters and the query AK Region and      */
1502 /* dynamically builds the SQL statement which forms the basis of the query.   */
1503 /******************************************************************************/
1504 FUNCTION get_drill_into_query(p_params_tbl       IN BIS_PMV_PAGE_PARAMETER_TBL,
1505                               p_ak_region_code   IN VARCHAR2)
1506                   return varchar2 IS
1507 
1508   l_sql_text          VARCHAR2(4000);
1509   l_sql_header        VARCHAR2(500);
1510   l_sql_query         VARCHAR2(4000);
1511   l_sql_footer        VARCHAR2(500);
1512 
1513 BEGIN
1514 
1515   l_sql_query  := build_drill_into_sql_stmt(p_params_tbl,p_ak_region_code);
1516   l_sql_header := make_sql_header;
1517   l_sql_footer := make_sql_footer;
1518   l_sql_text   := l_sql_header || g_rtn ||
1519                     '-- Made by drill into query' || g_rtn ||
1520                     l_sql_query || g_rtn ||
1521                     l_sql_footer;
1522 
1523   RETURN l_sql_text;
1524 
1525 EXCEPTION
1526 /* On error return the Error Message and Error Code */
1527  WHEN OTHERS THEN
1528    RETURN  '-- ' || SQLERRM || g_rtn ||
1529            '-- ' || SQLCODE;
1530 END get_drill_into_query;
1531 
1532 END HRI_OLTP_PMV_DYNSQLGEN;