DBA Data[Home] [Help]

PACKAGE BODY: APPS.HRI_BPL_TREND_TRM_SQL

Source


1 PACKAGE BODY hri_bpl_trend_trm_sql AS
2 /* $Header: hribttrm.pkb 120.3 2005/06/23 05:59:37 cbridge noship $ */
3 --
4 --
5 g_use_snapshot    BOOLEAN;
6 g_column_select   VARCHAR2(1000);
7 g_column_bucket   VARCHAR2(1000);
8 g_rtn             VARCHAR2(30) := '
9 ';
10 --
11 --
12 /******************************************************************************/
13 /* PROCESS FLOW                                                               */
14 /* ============                                                               */
15 /* The main entry point is the get_sql function. The processing is as follows */
16 /*                                                                            */
17 /* SELECT                                                                     */
18 /* ------                                                                     */
19 /* Templates for the measure columns are set by the set_metadata function.    */
20 /* Appropriate measures are then added to the select list using the template  */
21 /* depending on the input trend parameter record                              */
22 /*                                                                            */
23 /* A list of all the measure columns added is maintained and returned to the  */
24 /* calling function so that outer layers of SQL can reference all the columns */
25 /*                                                                            */
26 /* FROM                                                                       */
27 /* ----                                                                       */
28 /* The set_fact_table function in HRI_BPL_FACT_WRKFC_SQL is used to determine */
29 /* the appropriate fact object.                                               */
30 /*                                                                            */
31 /* WHERE                                                                      */
32 /* -----                                                                      */
33 /* set_conditions adds in any extra conditions required e.g. in top 4         */
34 /* countries a filter on the top 4 country codes is added                     */
35 /*                                                                            */
36 /* If the fact object is a snapshot MV then the date join will be an equality */
37 /* join rather than a between                                                 */
38 /*                                                                            */
39 /* SQL RETURNED                                                               */
40 /* ============                                                               */
41 /* The SQL is returned along with a list of all the measure columns in the    */
42 /* SELECT list:                                                               */
43 /*                                                                            */
44 /*   SELECT                                                                   */
45 /*    Period Id (Date)                                                        */
46 /*    Period Order                                                            */
47 /*    Measure Columns                                                         */
48 /*   FROM                                                                     */
49 /*    Table of periods to plot (sub-query)                                    */
50 /*    Snapshot/standard fact object                                           */
51 /*   WHERE                                                                    */
52 /*    Filter on selected manager                                              */
53 /*    Date filter (varies with snapshot/standard fact)                        */
54 /*    Additional filters (e.g. top 4 countries)                               */
55 /*                                                                            */
56 /* An outer layer of SQL is added for the TURNOVER calculation.               */
57 /* An outer layer of SQL is added that brings in periods with no data by      */
58 /* doing a UNION ALL with the trend periods table.                            */
59 /*                                                                            */
60 /******************************************************************************/
61 --
62 -- -------------------------------------------------------------------------
63 -- This procedure sets the select column templates for accessing the
64 -- turnover fact
65 -- -------------------------------------------------------------------------
66 --
67 PROCEDURE set_metadata IS
68   --
69 BEGIN
70   --
71 g_column_select := 'NVL(SUM(<measure>), 0)';
72 g_column_bucket :=
73 'NVL(SUM(CASE WHEN fact.<bucket> = <value>
74              THEN <measure>
75              ELSE 0
76         END), 0)';
77 --
78 END set_metadata;
79 --
80 --
81 -- -------------------------------------------------------------------------
82 -- This procedure is for future use only - applies dimension level parameter
83 -- conditions. Currently all trend reports are run from the main page which
84 -- does not have any additional parameters.
85 -- -------------------------------------------------------------------------
86 --
87 PROCEDURE analyze_parameters
88  (p_bind_tab         IN hri_oltp_pmv_util_param.HRI_PMV_BIND_TAB_TYPE,
89   p_fact_conditions  OUT NOCOPY VARCHAR2,
90   p_parameter_count  OUT NOCOPY PLS_INTEGER) IS
91 
92   l_parameter_name   VARCHAR2(100);
93 
94 BEGIN
95 
96 /* Initialize parameter count */
97   p_parameter_count := 0;
98 
99 /* Loop through parameters that have been set */
100   l_parameter_name := p_bind_tab.FIRST;
101 
102   WHILE (l_parameter_name IS NOT NULL) LOOP
103     IF (l_parameter_name = 'GEOGRAPHY+COUNTRY' OR
104         l_parameter_name = 'GEOGRAPHY+AREA' OR
105         l_parameter_name = 'JOB+JOB_FAMILY' OR
106         l_parameter_name = 'JOB+JOB_FUNCTION' OR
107         l_parameter_name = 'HRI_PRFRMNC+HRI_PRFMNC_RTNG_X' OR
108         l_parameter_name = 'HRI_PRSNTYP+HRI_WKTH_WKTYP' OR
109         l_parameter_name = 'HRI_LOW+HRI_LOW_BAND_X' OR
110         l_parameter_name = 'HRI_REASON+HRI_RSN_SEP_X' OR
111         l_parameter_name = 'HRI_WRKACTVT+HRI_WAC_SEPCAT_X') THEN
112 
113     /* Dynamically set conditions for parameter */
114       p_fact_conditions := p_fact_conditions ||
115         'AND fact.' || hri_mtdt_dim_lvl.g_dim_lvl_mtdt_tab
116                         (l_parameter_name).fact_viewby_col ||
117         ' IN (' || p_bind_tab(l_parameter_name).pmv_bind_string || ')' || g_rtn;
118 
119     /* Keep count of parameters set */
120       p_parameter_count := p_parameter_count + 1;
121 
122     END IF;
123 
124   /* Move to next parameter */
125     l_parameter_name := p_bind_tab.NEXT(l_parameter_name);
126 
127   END LOOP;
128 
129 END analyze_parameters;
130 --
131 -- -------------------------------------------------------------------------
132 -- This function returns a string which contains the columns in the fact
133 -- that have to be selected. The columns that are to be selected are
134 -- added using the column templates.
135 --
136 -- The column names of the columns added are stored in the measure column
137 -- table passed back to the calling package so that the columns can be
138 -- added to outer layers of SQL
139 -- -------------------------------------------------------------------------
140 --
141 PROCEDURE set_select
142  (p_parameter_rec   IN hri_oltp_pmv_util_param.HRI_PMV_PARAM_REC_TYPE,
143   p_bucket_dim      IN VARCHAR2,
144   p_include_sep     IN VARCHAR2,
145   p_include_sep_inv IN VARCHAR2,
146   p_include_sep_vol IN VARCHAR2,
147   p_select_sql      OUT NOCOPY VARCHAR2,
148   p_measure_columns OUT NOCOPY hri_oltp_pmv_query_trend.trend_measure_cols_type)
149 IS
150   --
151   -- template for bucket column
152   --
153   l_column_bucket  VARCHAR2(1000);
154   --
155   -- table of bucket values
156   --
157   l_bucket_tab        hri_mtdt_dim_lvl.dim_lvl_buckets_tabtype;
158   --
159   -- For forming the select statement
160   --
161   l_measure_trm   VARCHAR2(1000);
162   l_measure_inv   VARCHAR2(1000);
163   l_measure_vol   VARCHAR2(1000);
164   l_measure_count PLS_INTEGER;
165   --
166 BEGIN
167 -- Initialize measure count
168   l_measure_count := 0;
169 -- Check whether buckets are used
170   IF p_bucket_dim IS NOT NULL THEN
171 
172   -- Set the bucket column template to use the bucket column
173     l_column_bucket := REPLACE(g_column_bucket, '<bucket>',
174           hri_mtdt_dim_lvl.g_dim_lvl_mtdt_tab
175            (p_bucket_dim).fact_viewby_col);
176 
177   -- Get a pl/sql table containing the buckets for the given bucket dimension
178     IF (p_bucket_dim = 'HRI_LOW+HRI_LOW_BAND_X') THEN
179       hri_mtdt_dim_lvl.set_low_band_buckets(p_parameter_rec.wkth_wktyp_sk_fk);
180       l_bucket_tab := hri_mtdt_dim_lvl.g_low_band_buckets_tab;
181     ELSIF (p_bucket_dim = 'HRI_PRFRMNC+HRI_PRFMNC_RTNG_X') THEN
182       l_bucket_tab := hri_mtdt_dim_lvl.g_prfmnc_band_buckets_tab;
183     ELSIF (p_bucket_dim = 'GEOGRAPHY+COUNTRY') THEN
184       l_bucket_tab := hri_mtdt_dim_lvl.g_country_buckets_tab;
185     ELSIF (p_bucket_dim = 'HRI_PRSNTYP+HRI_WKTH_WKTYP') THEN
186       l_bucket_tab := hri_mtdt_dim_lvl.g_wkth_wktyp_tab;
187     END IF;
188   END IF;
189 
190   -- Add termination columns
191   IF (p_include_sep = 'Y') THEN
192     l_measure_trm := 'fact.separation_hdc';
193 
194     p_select_sql := p_select_sql || ',' || REPLACE(g_column_select,
195                                             '<measure>', l_measure_trm) ||
196                      '  period_sep_hdc' || g_rtn;
197 
198     -- Add column name to measure table
199     l_measure_count := l_measure_count + 1;
200     p_measure_columns(l_measure_count) := 'period_sep_hdc';
201 
202     -- Loop through buckets to add required columns
203     IF p_bucket_dim IS NOT NULL THEN
204       FOR i IN l_bucket_tab.FIRST..l_bucket_tab.LAST LOOP
205         p_select_sql := p_select_sql || ',' ||
206             REPLACE(REPLACE(l_column_bucket,
207                             '<measure>', l_measure_trm),
208                     '<value>', l_bucket_tab(i).bucket_id_string) ||
209            '  period_sep_hdc_' || l_bucket_tab(i).bucket_name || g_rtn;
210         -- Add column name to measure table
211         l_measure_count := l_measure_count + 1;
212         p_measure_columns(l_measure_count) := 'period_sep_hdc_' ||
213                                               l_bucket_tab(i).bucket_name;
214       END LOOP;
215     END IF;
216 
217   END IF;
218   --
219   -- Add Involuntary Termination columns
220   --
221   IF (p_include_sep_inv = 'Y') THEN
222     l_measure_inv := 'fact.sep_invol_hdc';
223 
224     p_select_sql := p_select_sql || ',' || REPLACE(g_column_select,
225                                             '<measure>', l_measure_inv) ||
226                      '  period_sep_invol_hdc' || g_rtn;
227 
228     -- Add column name to measure table
229     l_measure_count := l_measure_count + 1;
230     p_measure_columns(l_measure_count) := 'period_sep_invol_hdc';
231 
232     IF p_bucket_dim IS NOT NULL THEN
233 
234     /* Loop through bucket ids to add required columns */
235       FOR i IN l_bucket_tab.FIRST..l_bucket_tab.LAST LOOP
236         p_select_sql := p_select_sql || ',' ||
237             REPLACE(REPLACE(l_column_bucket,
238                             '<measure>', l_measure_inv),
239                     '<value>', l_bucket_tab(i).bucket_id_string) ||
240            '  period_sep_invol_hdc_' || l_bucket_tab(i).bucket_name || g_rtn;
241 
242         -- Add column name to measure table
243         l_measure_count := l_measure_count + 1;
244         p_measure_columns(l_measure_count) := 'period_sep_invol_hdc_' ||
245                                               l_bucket_tab(i).bucket_name;
246       END LOOP;
247 
248     END IF;
249 
250   END IF;
251   --
252   -- Add Voluntary Termination columns
253   --
254   IF (p_include_sep_vol = 'Y') THEN
255     l_measure_vol := 'fact.sep_vol_hdc';
256 
257     p_select_sql := p_select_sql || ',' || REPLACE(g_column_select,
258                                             '<measure>', l_measure_vol) ||
259                      '  period_sep_vol_hdc' || g_rtn;
260 
261     -- Add column name to measure table
262     l_measure_count := l_measure_count + 1;
263     p_measure_columns(l_measure_count) := 'period_sep_vol_hdc';
264 
265     IF p_bucket_dim IS NOT NULL THEN
266 
267     /* Loop through bucket ids to add required columns */
268       FOR i IN l_bucket_tab.FIRST..l_bucket_tab.LAST LOOP
269         p_select_sql := p_select_sql || ',' ||
270             REPLACE(REPLACE(l_column_bucket,
271                             '<measure>', l_measure_vol),
272                     '<value>', l_bucket_tab(i).bucket_id_string) ||
273            '  period_sep_vol_hdc_' || l_bucket_tab(i).bucket_name || g_rtn;
274         -- Add column name to measure table
275         l_measure_count := l_measure_count + 1;
276         p_measure_columns(l_measure_count) := 'period_sep_vol_hdc_' ||
277                                               l_bucket_tab(i).bucket_name;
278       END LOOP;
279 
280     END IF;
281 
282   END IF;
283   --
284 END set_select;
285 
286 --
287 -- -------------------------------------------------------------------------
288 -- This procedure returns conditions apart from the common conditions that
289 -- are present in a typical trend SQL.
290 -- -------------------------------------------------------------------------
291 --
292 PROCEDURE set_conditions(p_bucket_dim      IN VARCHAR2,
293                          p_fact_condition  IN OUT NOCOPY VARCHAR2)
294 IS
295   --
296   --
297 BEGIN
298   --
299   IF p_bucket_dim = 'GEOGRAPHY+COUNTRY' THEN
300     --
301     p_fact_condition := p_fact_condition ||
302 'AND fact.geo_country_code IN
303    (:GEO_COUNTRY_CODE1,
304     :GEO_COUNTRY_CODE2,
305     :GEO_COUNTRY_CODE3,
306     :GEO_COUNTRY_CODE4)' || g_rtn;
307     --
308   END IF;
309   --
310 END set_conditions;
311 --
312 -- -------------------------------------------------------------------------
313 -- This function returns the inner SQL that is required for generating the
314 -- headcount trend reports
315 -- -------------------------------------------------------------------------
316 --
317 PROCEDURE get_sql
318  (p_parameter_rec     IN hri_oltp_pmv_util_param.HRI_PMV_PARAM_REC_TYPE,
319   p_bind_tab          IN hri_oltp_pmv_util_param.HRI_PMV_BIND_TAB_TYPE,
320   p_trend_sql_params  IN hri_oltp_pmv_query_trend.trend_sql_params_type,
321   p_fact_sql          OUT NOCOPY VARCHAR2,
322   p_measure_columns   OUT NOCOPY hri_oltp_pmv_query_trend.trend_measure_cols_type)
323 IS
324   --
325   l_trend_periods_tbl VARCHAR2(32767);
326   l_select_sql        VARCHAR2(32767);
327   l_fact_table        VARCHAR2(50);
328   l_fact_condition    VARCHAR2(1000);
329   l_param_conditions  VARCHAR2(1000);
330   l_parameter_count   PLS_INTEGER;
331   l_parameter_rec     hri_oltp_pmv_util_param.HRI_PMV_PARAM_REC_TYPE;
332   --
333 BEGIN
334   --
335   -- Check whether a snapshot is available
336   --
337   g_use_snapshot := hri_oltp_pmv_util_snpsht.use_wcnt_chg_snpsht_for_mgr
338                      (p_supervisor_id => p_parameter_rec.peo_supervisor_id,
339                       p_effective_date => p_parameter_rec.time_curr_end_date);
340   --
341   -- -----------------------------------------------------------------------
342   -- SELECT CLAUSE
343   -- -----------------------------------------------------------------------
344   --
345   -- Set the column templates
346   --
347   set_metadata;
348   --
349   analyze_parameters
350    (p_bind_tab         => p_bind_tab,
351     p_fact_conditions  => l_param_conditions,
352     p_parameter_count  => l_parameter_count);
353   --
354   -- Add the columns required from the fact to the select clause
355   --
356   set_select
357    (p_parameter_rec => p_parameter_rec,
358     p_bucket_dim => p_trend_sql_params.bucket_dim,
359     p_include_sep => p_trend_sql_params.include_sep,
360     p_include_sep_vol => p_trend_sql_params.include_sep_vol,
361     p_include_sep_inv => p_trend_sql_params.include_sep_inv,
362     p_select_sql  => l_select_sql,
363     p_measure_columns => p_measure_columns);
364   --
365   -- -----------------------------------------------------------------------
366   -- FROM CLAUSE
367   -- -----------------------------------------------------------------------
368   --
369   -- Fetch the SQL for the table of periods
370   --
371   l_trend_periods_tbl :=
372 '(' || hri_oltp_pmv_query_time.get_time_clause
373         (p_past_trend   => p_trend_sql_params.past_trend,
374          p_future_trend => p_trend_sql_params.future_trend) || ')';
375   --
376   -- Set the fact table
377   --
378   l_parameter_rec := p_parameter_rec;
379   l_parameter_rec.view_by := 'HRI_PERSON+HRI_PER_USRDR_H';
380   hri_bpl_fact_sup_wcnt_chg_sql.set_fact_table
381    (p_parameter_rec => l_parameter_rec,
382     p_bucket_dim => p_trend_sql_params.bucket_dim,
383     p_include_hire => 'N',
384     p_include_trin => 'N',
385     p_include_trout => 'N',
386     p_include_term => 'N',
387     p_include_low => 'N',
388     p_parameter_count => 0,
389     p_single_param => NULL,
390     p_use_snapshot => g_use_snapshot,
391     p_fact_table => l_fact_table);
392   --
393   -- -----------------------------------------------------------------------
394   -- WHERE CLAUSE
395   -- -----------------------------------------------------------------------
396   --
397   -- Add direct record condition for old style fact tables
398   --
399   IF (l_fact_table = 'hri_mdp_sup_wcnt_chg_mv' OR
400       l_fact_table = 'hri_mds_sup_wcnt_chg_mv') THEN
401     l_fact_condition := l_fact_condition ||
402   'AND fact.direct_record_ind = 0' || g_rtn;
403   END IF;
404 
405   --
406   -- Set date join as equality if using snapshots
407   --
408   IF (g_use_snapshot) THEN
409     l_fact_condition := l_fact_condition ||
410 'AND fact.effective_date = tro.period_end_date
411 AND fact.comparison_type IN (''CURRENT'', ''SEQUENTIAL'', ''TREND'')
412 AND fact.period_type = &PERIOD_TYPE' || g_rtn;
413   ELSE
414     l_fact_condition := l_fact_condition ||
415 'AND fact.effective_date BETWEEN tro.period_start_date ' ||
416                         'AND tro.period_end_date' || g_rtn;
417   END IF;
418   --
419   -- Get the conditions for the where clause. Common conditions included in all
420   -- trend reports will not be fetched
421   --
422   set_conditions(p_bucket_dim     => p_trend_sql_params.bucket_dim,
423                  p_fact_condition => l_fact_condition);
424   --
425   -- -----------------------------------------------------------------------
426   -- BUILD THE SQL
427   -- -----------------------------------------------------------------------
428   --
429   p_fact_sql :=
430 'SELECT /*+ LEADING(tro) INDEX(fact) */
431  tro.period_as_of_date
432 ,tro.period_order' || g_rtn ||
433  l_select_sql ||
434 'FROM
435  '||l_trend_periods_tbl||'  tro
436 ,'||l_fact_table|| ' fact
437 WHERE fact.supervisor_person_id = &HRI_PERSON+HRI_PER_USRDR_H' || g_rtn ||
438  l_fact_condition ||
439  l_param_conditions ||
440 'GROUP BY
441  tro.period_order
442 ,tro.period_as_of_date';
443   --
444 END get_sql;
445 
446 END hri_bpl_trend_trm_sql;