DBA Data[Home] [Help]

PACKAGE BODY: APPS.HRI_BPL_DATA_SETUP_DGNSTC

Source


1 PACKAGE BODY hri_bpl_data_setup_dgnstc AS
2 /* $Header: hribdgdp.pkb 120.9 2006/12/13 05:44:45 msinghai noship $ */
3 
4 -- =========================================================================
5 --
6 -- OVERVIEW
7 -- --------
8 -- This package contains the procedure to test the data setup for DBI.
9 -- The checks that are included in the seeded diagnostics table are
10 -- performed
11 --
12 -- DOCUMENT REFERENCE
13 -- ------------------
14 -- http://files.oraclecorp.com/content/AllPublic/SharedFolders/HRMS%20
15 -- Intelligence%20(HRMSi)%20-%20Documents-Public/Design%20Specifications/
16 -- hri_lld_dgn_data_stup.doc
17 --
18 -- =========================================================================
19 
20 TYPE g_varchar2_tab_type IS TABLE OF VARCHAR2(240)
21                             INDEX BY BINARY_INTEGER;
22 g_object_name          VARCHAR2(100);
23 
24 -- ----------------------------------------------------------------------------
25 -- PROCEDURE output writes a message to the concurrent log
26 -- ----------------------------------------------------------------------------
27 PROCEDURE output(p_text  IN VARCHAR2) IS
28 
29 BEGIN
30 
31   hri_bpl_conc_log.output(p_text);
32 
33 END output;
34 
35 -- ----------------------------------------------------------------------------
36 -- PROCEDURE trim_msg removes blank spaces and enter characters from the string
37 --
38 -- INPUT PARAMETERS:
39 --          p_text: The text that has to be trimmed
40 -- ----------------------------------------------------------------------------
41 FUNCTION trim_msg(p_text IN VARCHAR2) RETURN VARCHAR2 IS
42 
43   l_text VARCHAR2(20000);
44 
45 BEGIN
46 
47   -- Remove blank spaces
48   l_text := TRIM(both ' ' FROM p_text);
49 
50   -- Remove Enter characters
51   l_text := TRIM(both fnd_global.local_chr(10) FROM l_text);
52 
53   RETURN l_text;
54 
55 END trim_msg;
56 
57 -- ----------------------------------------------------------------------------
58 -- Function GET_MESSAGE takes the message name and returns back the
59 -- message text
60 --
61 -- INPUT PARAMETERS:
62 --       p_message: Name of the message.
63 --
64 -- ----------------------------------------------------------------------------
65 FUNCTION get_message(p_message IN VARCHAR2) RETURN VARCHAR2 IS
66 
67 BEGIN
68 
69   IF p_message IS NULL THEN
70     RETURN NULL;
71   END IF;
72 
73   fnd_message.set_name('HRI', p_message);
74   --
75    IF HRI_BPL_SETUP_DIAGNOSTIC.is_token_exist(p_message,'PRODUCT_NAME') THEN
76     --
77     fnd_message.set_token('PRODUCT_NAME'
78                           ,HRI_BPL_SETUP_DIAGNOSTIC.get_product_name(p_object_name => g_object_name));
79     --
80   END IF;
81   --
82   RETURN trim_msg(fnd_message.get);
83 
84 END get_message;
85 
86 -- ----------------------------------------------------------------------------
87 -- Debugs a given supervisor loop
88 -- ----------------------------------------------------------------------------
89 PROCEDURE debug_sup_loop
90      (p_person_id       IN NUMBER,
91       p_effective_date  IN DATE,
92       p_loop_tab        OUT NOCOPY loop_results_tab_type) IS
93 
94   CURSOR sup_csr(p_psn_id   NUMBER,
95                  p_date     DATE) IS
96   SELECT
97    sub.full_name       sub_person_name
98   ,NVL(sub.employee_number, sub.npw_number)
99                        sub_emp_cwk_number
100   ,sup.full_name       sup_person_name
101   ,NVL(sup.employee_number, sup.npw_number)
102                        sup_emp_cwk_number
103   ,assg.supervisor_id  supervisor_id
104   FROM
105    per_all_assignments_f        assg
106   ,per_assignment_status_types  ast
107   ,per_people_x                 sup
108   ,per_people_x                 sub
109   WHERE assg.person_id = p_psn_id
110   AND p_date BETWEEN assg.effective_start_date
111              AND assg.effective_end_date
112   AND assg.assignment_status_type_id = ast.assignment_status_type_id
113   AND ast.per_system_status <> 'TERM_ASSIGN'
114   AND assg.primary_flag = 'Y'
115   AND assg.assignment_type IN ('E','C')
116   AND assg.person_id = sub.person_id
117   AND assg.supervisor_id = sup.person_id;
118 
119   l_loop_tab            loop_results_tab_type;
120   l_loop_rec            loop_results_rec_type;
121   l_sup_cache           g_varchar2_tab_type;
122   exit_loop             BOOLEAN;
123   l_person_id           NUMBER;
124   l_supervisor_id       NUMBER;
125   l_index               PLS_INTEGER;
126 
127 BEGIN
128 
129   -- Loop variable - will be set to true when a loop is encountered
130   --                 or when the end of the supervisor chains is reached
131   exit_loop := FALSE;
132 
133   -- Person to sample manager of
134   l_person_id := p_person_id;
135 
136   -- Update cache for encountering this person
137   l_sup_cache(l_person_id) := 'Y';
138 
139   -- Number of records in loop table
140   l_index := 0;
141 
142   -- Loop through supervisor levels
143   WHILE NOT exit_loop LOOP
144 
145     -- Fetch supervisor details for current person
146     OPEN sup_csr(l_person_id, p_effective_date);
147     FETCH sup_csr INTO
148       l_loop_rec.person_name,
149       l_loop_rec.person_number,
150       l_loop_rec.supervisor_name,
151       l_loop_rec.supervisor_number,
152       l_supervisor_id;
153 
154     -- Set next person id
155     IF (sup_csr%NOTFOUND OR sup_csr%NOTFOUND IS NULL) THEN
156       l_person_id := NULL;
157     ELSE
158       l_person_id := l_supervisor_id;
159       l_index := l_index + 1;
160       l_loop_tab(l_index) := l_loop_rec;
161     END IF;
162 
163     CLOSE sup_csr;
164 
165     BEGIN
166       -- Exit loop if no supervisor or a repeated supervisor
167       IF (l_person_id IS NULL) THEN
168         exit_loop := TRUE;
169       ELSIF (l_sup_cache(l_person_id) = 'Y') THEN
170         exit_loop := TRUE;
171       ELSE
172         RAISE NO_DATA_FOUND;
173       END IF;
174     EXCEPTION WHEN OTHERS THEN
175       l_sup_cache(l_person_id) := 'Y';
176     END;
177 
178   END LOOP;
179 
180   -- Output loop results
181   p_loop_tab := l_loop_tab;
182 
183 END debug_sup_loop;
184 
185 -- ----------------------------------------------------------------------------
186 -- Function returning the dynamic sql for the diagnostic
187 -- ----------------------------------------------------------------------------
188 FUNCTION get_dynamic_sql(p_dyn_sql_type   IN VARCHAR2,
189                          p_dyn_sql        IN VARCHAR2)
190             RETURN VARCHAR2 IS
191 
192   l_sql_string    VARCHAR2(32000);
193   l_sql_stmt      VARCHAR2(32000);
194 
195 BEGIN
196 
197   -- Check the sql type
198   IF (p_dyn_sql_type = 'API') THEN
199 
200     l_sql_stmt := 'SELECT ' || p_dyn_sql || ' FROM dual';
201 
202     BEGIN
203       EXECUTE IMMEDIATE l_sql_stmt INTO l_sql_string;
204     EXCEPTION WHEN OTHERS THEN
205       output('Error executing:  ' || l_sql_stmt);
206       RAISE;
207     END;
208 
209   ELSE
210 
211     l_sql_string := p_dyn_sql;
212 
213   END IF;
214 
215   RETURN l_sql_string;
216 
217 END get_dynamic_sql;
218 
219 -- ----------------------------------------------------------------------------
220 -- PROCEDURE set_bind_variables is used to set the bind variables that are
221 -- passed present in the dynamic sql.
222 -- ----------------------------------------------------------------------------
223 FUNCTION set_bind_variables(p_dyn_sql      IN VARCHAR2,
224                             p_start_date   IN DATE DEFAULT NULL,
225                             p_end_date     IN DATE DEFAULT NULL,
226                             p_obj_name     IN VARCHAR2 DEFAULT NULL)
227            RETURN VARCHAR2 IS
228 
229   l_start_date    VARCHAR2(80);
230   l_end_date      VARCHAR2(80);
231   l_dyn_sql       VARCHAR2(32000);
232 
233 BEGIN
234 
235   l_start_date := 'to_date(''' || to_char(p_start_date, 'DD/MM/YYYY') ||
236                            ''',''DD/MM/YYYY'')';
237   l_end_date := 'to_date(''' || to_char(p_end_date, 'DD/MM/YYYY') ||
238                          ''',''DD/MM/YYYY'')';
239 
240   l_dyn_sql := p_dyn_sql;
241   l_dyn_sql := replace(l_dyn_sql,':p_start_date', l_start_date);
242   l_dyn_sql := replace(l_dyn_sql,':p_end_date',   l_end_date);
243   l_dyn_sql := replace(l_dyn_sql,':p_obj_name',  '''' || p_obj_name || '''');
244   l_dyn_sql := replace(l_dyn_sql,':p_non_null',  '''x''');
245 
246   RETURN l_dyn_sql;
247 
248 END set_bind_variables;
249 
250 -- ----------------------------------------------------------------------------
251 -- Runs a data diagnostic
252 -- ----------------------------------------------------------------------------
253 PROCEDURE run_diagnostic
254      (p_object_name   IN VARCHAR2,
255       p_object_type   IN VARCHAR2,
256       p_mode          IN VARCHAR2,
257       p_start_date    IN DATE,
258       p_end_date      IN DATE,
259       p_row_limit     IN PLS_INTEGER,
260       p_results_tab   OUT NOCOPY data_results_tab_type,
261       p_impact        OUT NOCOPY BOOLEAN,
262       p_impact_msg    OUT NOCOPY VARCHAR2,
263       p_doc_links_url OUT NOCOPY VARCHAR2,
264       p_sql_stmt      OUT NOCOPY VARCHAR2) IS
265 
266   -- Cursor to get the diagnostic details
267   CURSOR diagnostic_csr IS
268   SELECT
269    stp.dynamic_sql
270   ,stp.dynamic_sql_type
271   ,stp.report_type
272   ,stp.default_mode
273   ,stp.impact_msg_name
274   FROM
275    hri_adm_dgnstc_setup  stp
276   WHERE stp.object_name = p_object_name
277   AND stp.object_type = p_object_type;
278 
279   -- Reference type cursor is used in Detail mode
280   TYPE ref_cursor_type   IS REF CURSOR;
281   c_records              ref_cursor_type;
282 
283   -- Column of results type
284   TYPE col_tab_type IS TABLE OF VARCHAR2(240) INDEX BY BINARY_INTEGER;
285 
286   -- Tables for results
287   l_results_tab     data_results_tab_type;
288   l_col1_tab        col_tab_type;
289   l_col2_tab        col_tab_type;
290   l_col3_tab        col_tab_type;
291   l_col4_tab        col_tab_type;
292   l_col5_tab        col_tab_type;
293 
294   l_row_limit       PLS_INTEGER;
295   l_sql_stmt        VARCHAR2(32000);
296   l_order_by_pos    PLS_INTEGER;
297   l_count           PLS_INTEGER;
298 
299 BEGIN
300 
301   -- Open diagnostic cursor
302   FOR diag_rec IN diagnostic_csr LOOP
303 
304     g_object_name := p_object_name;
305     -- Get the sql statement
306     IF (diag_rec.dynamic_sql IS NOT NULL) THEN
307       l_sql_stmt := get_dynamic_sql
308                      (p_dyn_sql_type => diag_rec.dynamic_sql_type,
309                       p_dyn_sql      => diag_rec.dynamic_sql);
310     ELSIF (diag_rec.report_type = 'ALERT') THEN
311       l_sql_stmt := hri_apl_dgnstc_core.get_alert_sql;
312     END IF;
313 
314     -- Set bind variables
315     l_sql_stmt := set_bind_variables
316                    (p_dyn_sql      => l_sql_stmt,
317                     p_start_date   => p_start_date,
318                     p_end_date     => p_end_date,
319                     p_obj_name     => p_object_name);
320 
321     -- Return SQL statement for display
322     -- Do not display the generic ALERT SQL
323     IF (diag_rec.dynamic_sql IS NOT NULL) THEN
324       p_sql_stmt := l_sql_stmt;
325     ELSIF (p_object_name = 'SUP_LOOP') THEN
326       p_sql_stmt := hri_apl_dgnstc_wrkfc.get_sup_loop_details;
327     END IF;
328 
329     -- Run the SQL in the appropriate mode
330     IF (diag_rec.default_mode = 'COUNT' OR
331          (diag_rec.default_mode = 'DETAIL_RESTRICT_COUNT' AND
332           p_mode = 'COUNT')) THEN
333 
334       -- In COUNT mode the dynamic sql should already be a count
335       -- otherwise add a count(*) and remove order clause
336       IF (diag_rec.default_mode <> 'COUNT') THEN
337 
338 	-- Find the last occurance of ORDER BY
339 	l_order_by_pos := INSTR(UPPER(l_sql_stmt), 'ORDER BY', -1, 1);
340 
341 	-- Remove order by if it exists
342 	IF (l_order_by_pos > 0) THEN
343 	  l_sql_stmt := SUBSTR(l_sql_stmt, 1, l_order_by_pos - 1);
344 	END IF;
345 
346 	-- Add count
347         l_sql_stmt := 'SELECT COUNT(*) FROM (' || l_sql_stmt || ')';
348 
349       END IF;
350 
351       -- Run the count
352       EXECUTE IMMEDIATE l_sql_stmt
353       INTO l_count;
354 
355       -- Store the count value
356       l_results_tab(1)(1) := to_char(l_count);
357 
358       -- If impact mesage is not null then store it
359       IF (diag_rec.impact_msg_name IS NOT NULL AND
360           l_count > 0) THEN
361 
362         -- Store impact
363         p_impact := TRUE;
364         p_impact_msg := get_message(diag_rec.impact_msg_name);
365 
366       ELSE
367 
368         -- No impact
369         p_impact := FALSE;
370 
371       END IF;
372 
373     -- In DETAIL mode
374     ELSE
375 
376       -- Add a row limit to the sql statement
377       IF (p_row_limit IS NOT NULL) THEN
378         l_row_limit := p_row_limit;
379       ELSE
380         l_row_limit := 2000;
381       END IF;
382 
383       -- Open the cursor for the results
384       OPEN c_records
385       FOR l_sql_stmt;
386 
387       -- store the column values
388       FETCH c_records BULK COLLECT
389       INTO  l_col1_tab,
390             l_col2_tab,
391             l_col3_tab,
392             l_col4_tab,
393             l_col5_tab
394       LIMIT l_row_limit;
395 
396       -- Close cursor
397       CLOSE c_records;
398 
399       -- Transfer results to master table
400       IF (l_col1_tab.EXISTS(1)) THEN
401         FOR i IN 1..l_col1_tab.LAST LOOP
402           l_results_tab(i)(1) := l_col1_tab(i);
403           l_results_tab(i)(2) := l_col2_tab(i);
404           l_results_tab(i)(3) := l_col3_tab(i);
405           l_results_tab(i)(4) := l_col4_tab(i);
406           l_results_tab(i)(5) := l_col5_tab(i);
407         END LOOP;
408       END IF;
409 
410       -- Store any impact
411       IF (diag_rec.impact_msg_name IS NOT NULL AND
412           l_count > 0) THEN
413 
414         -- Impact
415         p_impact := TRUE;
416         p_impact_msg := get_message(diag_rec.impact_msg_name);
417 
418       ELSE
419 
420         -- No impact
421         p_impact := FALSE;
422 
423       END IF;
424 
425     END IF;
426 
427   END LOOP;
428 
429   -- Return the results table
430   p_results_tab := l_results_tab;
431 
432 EXCEPTION WHEN OTHERS THEN
433 
434   output('Exception Raised in check_dbi_data_set_up');
435   output(SQLERRM);
436   output(SQLCODE);
437   RAISE;
438 
439 END run_diagnostic;
440 
441 END hri_bpl_data_setup_dgnstc;