DBA Data[Home] [Help]

APPS.PQH_GENERIC_PURGE dependencies on HR_UTILITY

Line 35: hr_utility.set_location('Entering '||l_proc,10);

31: WHERE short_name = p_short_name;
32: l_txn_catg_id NUMBER;
33: l_proc varchar2(80) := g_package||'get_transaction_category_id';
34: BEGIN
35: hr_utility.set_location('Entering '||l_proc,10);
36: OPEN csr_local_txn_catg;
37: FETCH csr_local_txn_catg INTO l_txn_catg_id;
38: CLOSE csr_local_txn_catg;
39: hr_utility.set_location('Leaving '||l_proc,20);

Line 39: hr_utility.set_location('Leaving '||l_proc,20);

35: hr_utility.set_location('Entering '||l_proc,10);
36: OPEN csr_local_txn_catg;
37: FETCH csr_local_txn_catg INTO l_txn_catg_id;
38: CLOSE csr_local_txn_catg;
39: hr_utility.set_location('Leaving '||l_proc,20);
40: RETURN l_txn_catg_id;
41: END get_transaction_category_id;
42:
43: PROCEDURE table_route_details(p_table_alias IN varchar2,

Line 71: hr_utility.set_location('Entering '||l_proc,10);

67:
68: l_proc varchar2(80) := g_package||'table_route_details';
69:
70: BEGIN
71: hr_utility.set_location('Entering '||l_proc,10);
72: OPEN csr_table_route(p_table_alias);
73: FETCH csr_table_route INTO p_table_route_id, p_from_clause, p_where_clause;
74: CLOSE csr_table_route;
75:

Line 81: hr_utility.set_location('leaving '||l_proc,20);

77: OPEN csr_col_name(p_table_route_id,'PRIMARY_KEY');
78: FETCH csr_col_name INTO p_primary_key_col;
79: CLOSE csr_col_name;
80: END IF;
81: hr_utility.set_location('leaving '||l_proc,20);
82: END table_route_details;
83:
84: PROCEDURE delete_wf_data(p_pk_value IN NUMBER) IS
85: l_proc varchar2(80) := g_package||'delete_wf_data';

Line 91: hr_utility.set_location('Entering '||l_proc,10);

87: l_item_key varchar2(80);
88: l_item_type Varchar2(30) := 'PQHGEN'; --Item type for PQH workflow
89: BEGIN
90: --
91: hr_utility.set_location('Entering '||l_proc,10);
92: --
93: hr_utility.set_location('Item Type PQHGEN',11);
94: hr_utility.set_location('Item Key '||g_wf_txn_catg_id||'-'||p_pk_value,12);
95: -- EXECUTE IMMEDIATE l_select INTO l_wf_txn_catg_id USING p_pk_value;

Line 93: hr_utility.set_location('Item Type PQHGEN',11);

89: BEGIN
90: --
91: hr_utility.set_location('Entering '||l_proc,10);
92: --
93: hr_utility.set_location('Item Type PQHGEN',11);
94: hr_utility.set_location('Item Key '||g_wf_txn_catg_id||'-'||p_pk_value,12);
95: -- EXECUTE IMMEDIATE l_select INTO l_wf_txn_catg_id USING p_pk_value;
96:
97: IF g_wf_txn_catg_id IS NOT NULL THEN

Line 94: hr_utility.set_location('Item Key '||g_wf_txn_catg_id||'-'||p_pk_value,12);

90: --
91: hr_utility.set_location('Entering '||l_proc,10);
92: --
93: hr_utility.set_location('Item Type PQHGEN',11);
94: hr_utility.set_location('Item Key '||g_wf_txn_catg_id||'-'||p_pk_value,12);
95: -- EXECUTE IMMEDIATE l_select INTO l_wf_txn_catg_id USING p_pk_value;
96:
97: IF g_wf_txn_catg_id IS NOT NULL THEN
98: --

Line 99: hr_utility.set_location('Deleting WF data '||l_proc,15);

95: -- EXECUTE IMMEDIATE l_select INTO l_wf_txn_catg_id USING p_pk_value;
96:
97: IF g_wf_txn_catg_id IS NOT NULL THEN
98: --
99: hr_utility.set_location('Deleting WF data '||l_proc,15);
100: --
101: l_item_key := g_wf_txn_catg_id||'-'||p_pk_value;
102: wf_engine.abortprocess(itemtype => l_item_type,
103: itemkey => l_item_key);

Line 109: hr_utility.set_location('Leaving '||l_proc,20);

105: ,itemkey => l_item_key);
106:
107:
108: END IF;
109: hr_utility.set_location('Leaving '||l_proc,20);
110: EXCEPTION
111: When No_data_found THEN
112: NULL;
113: WHEN Others THEN

Line 114: hr_utility.set_location('Error '||sqlErrm,16);

110: EXCEPTION
111: When No_data_found THEN
112: NULL;
113: WHEN Others THEN
114: hr_utility.set_location('Error '||sqlErrm,16);
115: hr_utility.set_location('Leaving '||L_proc,18);
116: END;
117:
118: PROCEDURE delete_process_log_data(p_pk_value IN Number ) IS

Line 115: hr_utility.set_location('Leaving '||L_proc,18);

111: When No_data_found THEN
112: NULL;
113: WHEN Others THEN
114: hr_utility.set_location('Error '||sqlErrm,16);
115: hr_utility.set_location('Leaving '||L_proc,18);
116: END;
117:
118: PROCEDURE delete_process_log_data(p_pk_value IN Number ) IS
119: CURSOR csr_process_log_id(p_txn_value IN NUMBER,

Line 136: hr_utility.set_location('Entering '||l_proc,10);

132: BEGIN
133: if g_short_name = 'BUDGET_WORKSHEET' THEN
134: g_short_name := 'APPROVE_WORKSHEET';
135: end if;
136: hr_utility.set_location('Entering '||l_proc,10);
137: FOR i IN csr_process_log_id(p_pk_value,g_short_name)
138: LOOP
139: pqh_process_log_api.delete_process_log
140: (p_validate => false

Line 146: hr_utility.set_location('Leaving '||l_proc,10);

142: ,p_object_version_number => i.object_version_number
143: ,p_effective_date => SYSDATE
144: );
145: END LOOP;
146: hr_utility.set_location('Leaving '||l_proc,10);
147: END;
148:
149: ----------------------------------------------------------------------------------------------------
150: -- PQH_GEN_PURGE TO CALL ALL OTHER PROCEDURES

Line 184: hr_utility.set_location('entering: ' ||l_proc,1000);

180: l_select varchar2(2000);
181:
182: BEGIN
183:
184: hr_utility.set_location('entering: ' ||l_proc,1000);
185: l_master_alias := p_alias;
186: g_master_alias := p_alias;
187: g_effective_date := p_effective_date;
188: --Added by kgowripe

Line 200: hr_utility.set_location('select stme:' || l_select_stmt,1010);

196: ,p_where_clause => l_where_clause_in_txn
197: ,p_primary_key_col => pk_col_name);
198:
199: l_select_stmt :='select ' || ' ' || ' TO_CHAR(' || pk_col_name || ')';
200: hr_utility.set_location('select stme:' || l_select_stmt,1010);
201: --
202: populate_pltable
203: (l_master_tab_route_id => l_master_tab_route_id,
204: paramname1 => paramname1,

Line 215: hr_utility.set_location('where_in:'||substr(l_where_clause_in_txn,1,100),1020);

211: paramvalue4 => paramvalue4,
212: paramname5 => paramname5,
213: paramvalue5 => paramvalue5);
214: --
215: hr_utility.set_location('where_in:'||substr(l_where_clause_in_txn,1,100),1020);
216: hr_utility.set_location('where_in:'||substr(l_where_clause_in_txn,100,100),1021);
217: --
218: pqh_refresh_data.replace_where_params_purge
219: (p_where_clause_in => l_where_clause_in_txn,

Line 216: hr_utility.set_location('where_in:'||substr(l_where_clause_in_txn,100,100),1021);

212: paramname5 => paramname5,
213: paramvalue5 => paramvalue5);
214: --
215: hr_utility.set_location('where_in:'||substr(l_where_clause_in_txn,1,100),1020);
216: hr_utility.set_location('where_in:'||substr(l_where_clause_in_txn,100,100),1021);
217: --
218: pqh_refresh_data.replace_where_params_purge
219: (p_where_clause_in => l_where_clause_in_txn,
220: p_txn_tab_flag => 'N',

Line 224: hr_utility.set_location('where_out:'||substr(l_where_clause_out_txn,1,75),1023);

220: p_txn_tab_flag => 'N',
221: p_txn_id => '',
222: p_where_clause_out => l_where_clause_out_txn );
223: --
224: hr_utility.set_location('where_out:'||substr(l_where_clause_out_txn,1,75),1023);
225: hr_utility.set_location('where_out:'||substr(l_where_clause_out_txn,75,75),1024);
226: --
227: pqh_refresh_data.get_all_rows
228: (p_select_stmt => l_select_stmt,

Line 225: hr_utility.set_location('where_out:'||substr(l_where_clause_out_txn,75,75),1024);

221: p_txn_id => '',
222: p_where_clause_out => l_where_clause_out_txn );
223: --
224: hr_utility.set_location('where_out:'||substr(l_where_clause_out_txn,1,75),1023);
225: hr_utility.set_location('where_out:'||substr(l_where_clause_out_txn,75,75),1024);
226: --
227: pqh_refresh_data.get_all_rows
228: (p_select_stmt => l_select_stmt,
229: p_from_clause => l_from_clause_txn,

Line 244: hr_utility.set_location('wf_txn_catg_id '||g_wf_txn_catg_id,12);

240: savepoint s1;
241: l_select := 'SELECT wf_transaction_category_id '||' FROM '||l_from_clause_txn||' WHERE '||pk_col_name||' = :1';
242:
243: EXECUTE IMMEDIATE l_select INTO g_wf_txn_catg_id USING l_parent_pk_value;
244: hr_utility.set_location('wf_txn_catg_id '||g_wf_txn_catg_id,12);
245: --
246: del_child_records(l_master_alias ,l_parent_pk_value );
247: --
248: enter_conc_log(p_pk_value => l_parent_pk_value,

Line 269: hr_utility.set_location('leaving: ' ||l_proc,1100);

265: fnd_file.put(fnd_file.log,fnd_message.get);
266: fnd_file.put_line(fnd_file.log,' ');
267: commit;
268: END LOOP;
269: hr_utility.set_location('leaving: ' ||l_proc,1100);
270:
271: END pqh_gen_purge;
272: -----------------------------------------------------------------------------------------
273: -- FUNCTION GET_COL_TYPE

Line 324: hr_utility.set_location('entering: ' ||l_proc,1200);

320: paramvalue5 IN VARCHAR2) IS
321: l_proc varchar2(72) := g_package||'populate_pltable';
322: i number := 1;
323: BEGIN
324: hr_utility.set_location('entering: ' ||l_proc,1200);
325: pqh_refresh_data.g_refresh_tab.DELETE;
326: --populate the g_refresh_tab to be used in replace_where_params_purge
327: pqh_refresh_data.g_refresh_tab(1).column_name := paramname1;
328: hr_utility.set_location(paramname1||'-'||get_col_type(paramname1,l_master_tab_route_id)||'-'||l_master_tab_route_id,1201);

Line 328: hr_utility.set_location(paramname1||'-'||get_col_type(paramname1,l_master_tab_route_id)||'-'||l_master_tab_route_id,1201);

324: hr_utility.set_location('entering: ' ||l_proc,1200);
325: pqh_refresh_data.g_refresh_tab.DELETE;
326: --populate the g_refresh_tab to be used in replace_where_params_purge
327: pqh_refresh_data.g_refresh_tab(1).column_name := paramname1;
328: hr_utility.set_location(paramname1||'-'||get_col_type(paramname1,l_master_tab_route_id)||'-'||l_master_tab_route_id,1201);
329: if get_col_type(paramname1,l_master_tab_route_id) = 'D' then
330: pqh_refresh_data.g_refresh_tab(1).txn_val := ' fnd_date.canonical_to_date('''||paramvalue1||''')';
331: pqh_refresh_data.g_refresh_tab(1).column_type := 'N';
332: else

Line 337: hr_utility.set_location(paramname2||'-'||get_col_type(paramname2,l_master_tab_route_id)||'-'||l_master_tab_route_id,1202);

333: pqh_refresh_data.g_refresh_tab(1).txn_val := paramvalue1;
334: pqh_refresh_data.g_refresh_tab(1).column_type := get_col_type(paramname1,l_master_tab_route_id);
335: end if;
336: pqh_refresh_data.g_refresh_tab(2).column_name := paramname2;
337: hr_utility.set_location(paramname2||'-'||get_col_type(paramname2,l_master_tab_route_id)||'-'||l_master_tab_route_id,1202);
338: if get_col_type(paramname2,l_master_tab_route_id) = 'D' then
339: pqh_refresh_data.g_refresh_tab(2).txn_val := ' fnd_date.canonical_to_date('''||paramvalue2||''')';
340: pqh_refresh_data.g_refresh_tab(2).column_type := 'N';
341: else

Line 346: hr_utility.set_location(paramname3||'-'||get_col_type(paramname3,l_master_tab_route_id)||'-'||l_master_tab_route_id,1203);

342: pqh_refresh_data.g_refresh_tab(2).txn_val := paramvalue2;
343: pqh_refresh_data.g_refresh_tab(2).column_type := get_col_type(paramname2,l_master_tab_route_id);
344: end if;
345: pqh_refresh_data.g_refresh_tab(3).column_name := paramname3;
346: hr_utility.set_location(paramname3||'-'||get_col_type(paramname3,l_master_tab_route_id)||'-'||l_master_tab_route_id,1203);
347: if get_col_type(paramname3,l_master_tab_route_id) = 'D' then
348: pqh_refresh_data.g_refresh_tab(3).txn_val := ' fnd_date.canonical_to_date('''||paramvalue3||''')';
349: pqh_refresh_data.g_refresh_tab(3).column_type := 'N';
350: else

Line 355: hr_utility.set_location(paramname4||'-'||get_col_type(paramname4,l_master_tab_route_id)||'-'||l_master_tab_route_id,1204);

351: pqh_refresh_data.g_refresh_tab(3).txn_val := paramvalue3;
352: pqh_refresh_data.g_refresh_tab(3).column_type := get_col_type(paramname3,l_master_tab_route_id);
353: end if;
354: pqh_refresh_data.g_refresh_tab(4).column_name := paramname4;
355: hr_utility.set_location(paramname4||'-'||get_col_type(paramname4,l_master_tab_route_id)||'-'||l_master_tab_route_id,1204);
356: if get_col_type(paramname4,l_master_tab_route_id) = 'D' then
357: pqh_refresh_data.g_refresh_tab(4).txn_val := ' fnd_date.canonical_to_date('''||paramvalue4||''')';
358: pqh_refresh_data.g_refresh_tab(4).column_type := 'N';
359: else

Line 364: hr_utility.set_location(paramname5||'-'||get_col_type(paramname5,l_master_tab_route_id)||'-'||l_master_tab_route_id,1205);

360: pqh_refresh_data.g_refresh_tab(4).txn_val := paramvalue4;
361: pqh_refresh_data.g_refresh_tab(4).column_type := get_col_type(paramname4,l_master_tab_route_id);
362: end if;
363: pqh_refresh_data.g_refresh_tab(5).column_name := paramname5;
364: hr_utility.set_location(paramname5||'-'||get_col_type(paramname5,l_master_tab_route_id)||'-'||l_master_tab_route_id,1205);
365: if get_col_type(paramname5,l_master_tab_route_id) = 'D' then
366: pqh_refresh_data.g_refresh_tab(5).txn_val := ' fnd_date.canonical_to_date('''||paramvalue5||''')';
367: pqh_refresh_data.g_refresh_tab(5).column_type := 'N';
368: else

Line 378: hr_utility.set_location(pqh_refresh_data.g_refresh_tab(i).column_name,10);

374: FOR i IN 1..5 LOOP
375: If pqh_refresh_data.g_refresh_tab(i).column_name = 'SHORT_NAME' THEN
376: g_short_name:= pqh_refresh_data.g_refresh_tab(i).txn_val;
377: END IF;
378: hr_utility.set_location(pqh_refresh_data.g_refresh_tab(i).column_name,10);
379: hr_utility.set_location(pqh_refresh_data.g_refresh_tab(i).column_type,11);
380: hr_utility.set_location(pqh_refresh_data.g_refresh_tab(i).txn_val,12);
381: END LOOP;
382: hr_utility.set_location('leaving: ' ||l_proc,1300);

Line 379: hr_utility.set_location(pqh_refresh_data.g_refresh_tab(i).column_type,11);

375: If pqh_refresh_data.g_refresh_tab(i).column_name = 'SHORT_NAME' THEN
376: g_short_name:= pqh_refresh_data.g_refresh_tab(i).txn_val;
377: END IF;
378: hr_utility.set_location(pqh_refresh_data.g_refresh_tab(i).column_name,10);
379: hr_utility.set_location(pqh_refresh_data.g_refresh_tab(i).column_type,11);
380: hr_utility.set_location(pqh_refresh_data.g_refresh_tab(i).txn_val,12);
381: END LOOP;
382: hr_utility.set_location('leaving: ' ||l_proc,1300);
383: END populate_pltable;

Line 380: hr_utility.set_location(pqh_refresh_data.g_refresh_tab(i).txn_val,12);

376: g_short_name:= pqh_refresh_data.g_refresh_tab(i).txn_val;
377: END IF;
378: hr_utility.set_location(pqh_refresh_data.g_refresh_tab(i).column_name,10);
379: hr_utility.set_location(pqh_refresh_data.g_refresh_tab(i).column_type,11);
380: hr_utility.set_location(pqh_refresh_data.g_refresh_tab(i).txn_val,12);
381: END LOOP;
382: hr_utility.set_location('leaving: ' ||l_proc,1300);
383: END populate_pltable;
384: ----------------------------------------------------------------------------------------------

Line 382: hr_utility.set_location('leaving: ' ||l_proc,1300);

378: hr_utility.set_location(pqh_refresh_data.g_refresh_tab(i).column_name,10);
379: hr_utility.set_location(pqh_refresh_data.g_refresh_tab(i).column_type,11);
380: hr_utility.set_location(pqh_refresh_data.g_refresh_tab(i).txn_val,12);
381: END LOOP;
382: hr_utility.set_location('leaving: ' ||l_proc,1300);
383: END populate_pltable;
384: ----------------------------------------------------------------------------------------------
385: -- DEL_CHILD_RECORDS
386: ----------------------------------------------------------------------------------------------

Line 423: hr_utility.set_location('entering: ' ||l_proc,1500);

419: START WITH parent_node_type = UPPER(p_alias_name)
420: CONNECT BY parent_node_type = PRIOR child_node_type;
421:
422: BEGIN
423: hr_utility.set_location('entering: ' ||l_proc,1500);
424: l_parent_pk_value := p_parent_pk_value;
425: l_alias_name := p_alias_name;
426: OPEN csr_child_alias(l_alias_name);
427: LOOP

Line 462: hr_utility.set_location('Parent key value '||l_parent_pk_value,20);

458: ,p_where_clause => l_where_clause_in_txn
459: ,p_primary_key_col => c_pk_col_name);
460:
461: l_select_stmt :='select '|| c_pk_col_name ;
462: hr_utility.set_location('Parent key value '||l_parent_pk_value,20);
463: pqh_refresh_data.replace_where_params_purge
464: ( p_where_clause_in => l_where_clause_in_txn,
465: p_txn_tab_flag => 'Y',
466: p_txn_id => l_parent_pk_value,

Line 478: hr_utility.set_location('Child alias '||l_child_alias,20);

474: p_total_rows => l_tot_txn_rows,
475: p_all_txn_rows => l_all_child_rows_array );
476: FOR i in NVL(l_all_child_rows_array.FIRST,0)..NVL(l_all_child_rows_array.LAST,-1)
477: LOOP
478: hr_utility.set_location('Child alias '||l_child_alias,20);
479: hr_utility.set_location('child pk '||l_all_child_rows_array(i),25);
480: del_child_records(l_child_alias,l_all_child_rows_array(i));
481: hr_utility.set_location('Deleting Child alias '||l_child_alias,20);
482: hr_utility.set_location('Deleting child pk '||l_all_child_rows_array(i),25);

Line 479: hr_utility.set_location('child pk '||l_all_child_rows_array(i),25);

475: p_all_txn_rows => l_all_child_rows_array );
476: FOR i in NVL(l_all_child_rows_array.FIRST,0)..NVL(l_all_child_rows_array.LAST,-1)
477: LOOP
478: hr_utility.set_location('Child alias '||l_child_alias,20);
479: hr_utility.set_location('child pk '||l_all_child_rows_array(i),25);
480: del_child_records(l_child_alias,l_all_child_rows_array(i));
481: hr_utility.set_location('Deleting Child alias '||l_child_alias,20);
482: hr_utility.set_location('Deleting child pk '||l_all_child_rows_array(i),25);
483: call_delete_api

Line 481: hr_utility.set_location('Deleting Child alias '||l_child_alias,20);

477: LOOP
478: hr_utility.set_location('Child alias '||l_child_alias,20);
479: hr_utility.set_location('child pk '||l_all_child_rows_array(i),25);
480: del_child_records(l_child_alias,l_all_child_rows_array(i));
481: hr_utility.set_location('Deleting Child alias '||l_child_alias,20);
482: hr_utility.set_location('Deleting child pk '||l_all_child_rows_array(i),25);
483: call_delete_api
484: (p_tab_route_id => l_tab_route_id,
485: p_pk_value => l_all_child_rows_array(i),

Line 482: hr_utility.set_location('Deleting child pk '||l_all_child_rows_array(i),25);

478: hr_utility.set_location('Child alias '||l_child_alias,20);
479: hr_utility.set_location('child pk '||l_all_child_rows_array(i),25);
480: del_child_records(l_child_alias,l_all_child_rows_array(i));
481: hr_utility.set_location('Deleting Child alias '||l_child_alias,20);
482: hr_utility.set_location('Deleting child pk '||l_all_child_rows_array(i),25);
483: call_delete_api
484: (p_tab_route_id => l_tab_route_id,
485: p_pk_value => l_all_child_rows_array(i),
486: p_from_clause_txn => l_from_clause_txn,

Line 493: hr_utility.set_location('leaving: ' ||l_proc,1600);

489:
490: END LOOP;
491: END LOOP;
492: CLOSE csr_child_alias;
493: hr_utility.set_location('leaving: ' ||l_proc,1600);
494: END del_child_records;
495: -----------------------------------------------------------------------------------------
496: -- CALL_DELETE_API
497: ------------------------------------------------------------------------------------------

Line 544: hr_utility.set_location('entering: ' ||l_proc,1700);

540: l_pk_col_name PQH_ATTRIBUTES.COLUMN_NAME%TYPE;
541: l_process_log_id NUMBER;
542: -----------------------------------------------------------------------------------------
543: BEGIN
544: hr_utility.set_location('entering: ' ||l_proc,1700);
545: l_pk_value := p_pk_value;
546: l_pk_col_name := p_pk_col_name;
547: -- l_plog_value.DELETE;
548: -- l_ovn_value.DELETE;

Line 578: hr_utility.set_location('l_dummy_in'||substr(l_dummy_in,1,50),1710);

574: --
575: OPEN csr_delete_api_name(p_tab_route_id);
576: FETCH csr_delete_api_name INTO l_dummy_in;
577: CLOSE csr_delete_api_name;
578: hr_utility.set_location('l_dummy_in'||substr(l_dummy_in,1,50),1710);
579: hr_utility.set_location('l_dummy_in'||substr(l_dummy_in,51,50),1720);
580: -- l_dummy_in := replace(l_dummy_in, 'R_OBJECT_VERSION_NUMBER' , l_ovn_value(1));
581:
582: l_dummy_in := replace(l_dummy_in, '', g_effective_date);

Line 579: hr_utility.set_location('l_dummy_in'||substr(l_dummy_in,51,50),1720);

575: OPEN csr_delete_api_name(p_tab_route_id);
576: FETCH csr_delete_api_name INTO l_dummy_in;
577: CLOSE csr_delete_api_name;
578: hr_utility.set_location('l_dummy_in'||substr(l_dummy_in,1,50),1710);
579: hr_utility.set_location('l_dummy_in'||substr(l_dummy_in,51,50),1720);
580: -- l_dummy_in := replace(l_dummy_in, 'R_OBJECT_VERSION_NUMBER' , l_ovn_value(1));
581:
582: l_dummy_in := replace(l_dummy_in, '', g_effective_date);
583: pqh_refresh_data.replace_where_params_purge

Line 589: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,1,50),1750);

585: p_txn_tab_flag => 'Y',
586: p_txn_id => l_pk_value,
587: p_where_clause_out => l_dummy_out);
588: --
589: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,1,50),1750);
590: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,51,50),1760);
591: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,101,50),1770);
592: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,151,50),1780);
593: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,201,50),1790);

Line 590: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,51,50),1760);

586: p_txn_id => l_pk_value,
587: p_where_clause_out => l_dummy_out);
588: --
589: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,1,50),1750);
590: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,51,50),1760);
591: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,101,50),1770);
592: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,151,50),1780);
593: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,201,50),1790);
594: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,251,50),1800);

Line 591: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,101,50),1770);

587: p_where_clause_out => l_dummy_out);
588: --
589: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,1,50),1750);
590: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,51,50),1760);
591: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,101,50),1770);
592: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,151,50),1780);
593: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,201,50),1790);
594: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,251,50),1800);
595: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,301,50),1810);

Line 592: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,151,50),1780);

588: --
589: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,1,50),1750);
590: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,51,50),1760);
591: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,101,50),1770);
592: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,151,50),1780);
593: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,201,50),1790);
594: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,251,50),1800);
595: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,301,50),1810);
596: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,351,50),1820);

Line 593: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,201,50),1790);

589: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,1,50),1750);
590: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,51,50),1760);
591: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,101,50),1770);
592: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,151,50),1780);
593: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,201,50),1790);
594: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,251,50),1800);
595: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,301,50),1810);
596: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,351,50),1820);
597: --Execute the procedure to delete the record with passed PK value.

Line 594: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,251,50),1800);

590: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,51,50),1760);
591: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,101,50),1770);
592: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,151,50),1780);
593: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,201,50),1790);
594: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,251,50),1800);
595: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,301,50),1810);
596: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,351,50),1820);
597: --Execute the procedure to delete the record with passed PK value.
598: l_dummy_out1 := substr(l_dummy_out,1,instr(l_dummy_out,'R_OBJECT_VERSION_NUMBER')-1 );

Line 595: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,301,50),1810);

591: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,101,50),1770);
592: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,151,50),1780);
593: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,201,50),1790);
594: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,251,50),1800);
595: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,301,50),1810);
596: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,351,50),1820);
597: --Execute the procedure to delete the record with passed PK value.
598: l_dummy_out1 := substr(l_dummy_out,1,instr(l_dummy_out,'R_OBJECT_VERSION_NUMBER')-1 );
599: l_dummy_out2 := substr(l_dummy_out,instr(l_dummy_out,'R_OBJECT_VERSION_NUMBER') +length('R_OBJECT_VERSION_NUMBER'),length(l_dummy_out));

Line 596: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,351,50),1820);

592: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,151,50),1780);
593: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,201,50),1790);
594: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,251,50),1800);
595: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,301,50),1810);
596: hr_utility.set_location('l_dummy_out'||substr(l_dummy_out,351,50),1820);
597: --Execute the procedure to delete the record with passed PK value.
598: l_dummy_out1 := substr(l_dummy_out,1,instr(l_dummy_out,'R_OBJECT_VERSION_NUMBER')-1 );
599: l_dummy_out2 := substr(l_dummy_out,instr(l_dummy_out,'R_OBJECT_VERSION_NUMBER') +length('R_OBJECT_VERSION_NUMBER'),length(l_dummy_out));
600:

Line 618: hr_utility.set_location('leaving: ' ||l_proc,1900);

614: 'p_ovn' ||
615: l_dummy_out2|| ';'||
616: 'END;' ;
617:
618: hr_utility.set_location('leaving: ' ||l_proc,1900);
619:
620: EXCEPTION
621: WHEN OTHERS THEN
622: hr_utility.set_location(SQLERRM,15);

Line 622: hr_utility.set_location(SQLERRM,15);

618: hr_utility.set_location('leaving: ' ||l_proc,1900);
619:
620: EXCEPTION
621: WHEN OTHERS THEN
622: hr_utility.set_location(SQLERRM,15);
623: -- retcode:=2;
624: rollback to s1;
625: g_error_flag := TRUE;
626: --