DBA Data[Home] [Help]

PACKAGE BODY: APPS.CS_KB_CONC_PROG_PKG

Source


1 PACKAGE BODY cs_kb_conc_prog_pkg AS
2 /* $Header: csksynib.pls 120.2.12010000.3 2009/10/15 06:54:13 amganapa ship $ */
3 
4   /* errbuf = err messages
5      retcode = 0 SUCCESS, 1 = warning, 2=error
6   */
7 
8   /* bmode: S = sync  OFAST=optimize fast, OFULL = optimize full,
9             R = REBUILD, DR = DROP/Recreate
10   */
11 
12   -- **********************
13   --  PRIVATE DECLARATIONS
14   -- **********************
15 
16   invalid_mode_error EXCEPTION;
17   invalid_action_error EXCEPTION;
18   drop_index_error     EXCEPTION;
19   create_index_error   EXCEPTION;
20   rebuild_cache_error  EXCEPTION;
21 
22   g_cs_short_name   VARCHAR2(10) := UPPER('CS'); -- set at patching
26   --This flag was set to Y to fix bug 8757484
23   g_apps_short_name VARCHAR2(10) := UPPER('APPS'); -- set at patching
24   -- New for bug 4321268
25   G_BATCH_SIZE      NUMBER := 10000;
27   attachment_flag  VARCHAR2(3):= 'Y'; --12.1.3
28 
29    -- New internal procedures for bug 4321268
30   /*
31    *   Populate solution text index.
32    *
33    */
34   PROCEDURE populate_set_index (
35 		    x_msg_error     OUT NOCOPY VARCHAR2,
36   	            x_return_status OUT NOCOPY VARCHAR2
37 		   )
38   IS
39    CURSOR all_published_solutions IS
40      SELECT tl.rowid -- tl.set_id
41      FROM cs_kb_sets_tl tl, cs_kb_sets_b b
42      WHERE b.set_id = tl.set_id
43      AND b.status = 'PUB';
44 
45 
46     TYPE l_rowid_type IS TABLE OF ROWID INDEX BY BINARY_INTEGER;
47     l_rowid_list      l_rowid_type;
48 
49     l_soln_comp_index VARCHAR2(250) := 'CS_KB_SETS_TL_N3';
50      l_soln_comp_attach_index VARCHAR2(250) := 'CS_KB_SETS_ATTACH_TL_N3';  --12.1.3
51 
52   BEGIN
53   --12.1.3
54             IF FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL THEN
55        FND_LOG.STRING(FND_LOG.LEVEL_STATEMENT, 'csk.plsql.cs_kb_conc_prog_pkg.populate_set_index',
56                      ' attachment_flag:'||attachment_flag);
57     END IF;
58 
59 
60 
61       IF FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL THEN
62        FND_LOG.STRING(FND_LOG.LEVEL_STATEMENT, 'csk.plsql.cs_kb_conc_prog_pkg.populate_set_index',
63                      'l_soln_comp_index:'||l_soln_comp_index);
64     END IF;
65   --12.1.3
66     x_return_status := fnd_api.G_RET_STS_SUCCESS;
67 
68     -- Fetch out the list of IDs for all published solutions
69     OPEN all_published_solutions;
70     LOOP
71         FETCH all_published_solutions BULK COLLECT INTO l_rowid_list limit G_BATCH_SIZE;
72 	--12.1.3
73 	--The else condition was commented to fix bug 8757484
74 	IF attachment_flag = 'Y' THEN
75 		FORALL i IN l_rowid_list.FIRST..l_rowid_list.LAST
76 
77 		  UPDATE cs_kb_sets_tl
78 		  SET composite_assoc_attach_index = 'R'
79 		  WHERE rowid = l_rowid_list(i);
80 	--ELSE
81 		FORALL i IN l_rowid_list.FIRST..l_rowid_list.LAST
82 		  UPDATE cs_kb_sets_tl
83 		  SET composite_assoc_index = 'R'
84 		  WHERE rowid = l_rowid_list(i);
85         END IF;
86         --12.1.3
87         COMMIT;
88     /*
89         -- click off the sync. program
90         launch_sync_request(
91                    p_mode              => 'S',
92                    p_conc_request_name => 'CS_KB_SYNC_SOLUTIONS_INDEX',
93 		   x_msg_error         => x_msg_error,
94 		   x_return_status     => x_return_status );
95 
96         IF x_return_status != fnd_api.G_RET_STS_SUCCESS THEN
97           EXIT;
98         END IF;
99 
100         x_return_status := fnd_api.G_RET_STS_SUCCESS;
101      */
102 
103         -- Check if all_published_solutions is notfound.
104         -- NOTE: this check should come at the end because for the last batch
105         -- the total number of sets being fetched may be less than the l_batch_size.
106         -- If l_set_id_list is not filled with the exact number as the l_batch_size,
107         -- all_published_solutons%notfound is true. Putting this at the end
108         -- guarantees we process the last batch.
109          EXIT WHEN all_published_solutions%NOTFOUND;
110     END LOOP;
111     CLOSE all_published_solutions;
112     Sync_index( l_soln_comp_index, 'S', 0 );
113 --12.1.3
114    --Commented to fix bug 8757484
115    --IF attachment_flag = 'Y' THEN
116      Sync_index( l_soln_comp_attach_index, 'S', 0 );
117   -- END IF;
118  --12.1.3
119   EXCEPTION
120     WHEN OTHERS  THEN
121       ROLLBACK; -- do not use savepoint because savepoint is cleared when commit.
122       x_msg_error := 'populate_set_index: '
123 	  ||fnd_message.GET_STRING('CS','CS_KB_C_UNEXP_ERR')||' '||SQLERRM;
124       x_return_status := fnd_api.G_RET_STS_ERROR;
125   END populate_set_index;
126 
127   /*
128    *   Populate element text index.
129    *
130    */
131   PROCEDURE populate_element_index (
132 	   x_msg_error     OUT NOCOPY VARCHAR2,
133 	   x_return_status OUT NOCOPY VARCHAR2
134 		   )
135   IS
136       l_statement_comp_index VARCHAR2(250) := 'CS_KB_ELEMENTS_TL_N2';
137   BEGIN
138     x_return_status := fnd_api.G_RET_STS_SUCCESS;
139 
140     SAVEPOINT populate_element_index_SAV;
141 
142     -- We do not use bulk update in this case because the concurrent request
143     -- is incompatbile with itself. Even we kick off the sync. request, it
144     -- will be in pending status until "DR" or "R" request is finished. So,
145     UPDATE /*+ parallel(t) */ cs_kb_elements_tl t
146     SET t.composite_text_index = 'B';
147 
148     COMMIT;
149 
150     -- Reestablish savepoint, as commit cleared it.
151     SAVEPOINT populate_element_index_SAV;
152 
153     -- Start synchronizing index.
154     Sync_index( l_statement_comp_index, 'S', 0 );
155 
156   EXCEPTION
157     WHEN OTHERS  THEN
158       ROLLBACK TO populate_element_index_SAV;
159       x_msg_error := 'populate_element_index: '
160 	  ||fnd_message.GET_STRING('CS','CS_KB_C_UNEXP_ERR')||' '||SQLERRM;
161       x_return_status := fnd_api.G_RET_STS_ERROR;
162   END populate_element_index;
163 
164 
165   /*
166    *   Populate soluton categories text index.
167    *
168    */
169   PROCEDURE populate_soln_cat_index (
170   	        x_msg_error     OUT NOCOPY VARCHAR2,
171  	     	x_return_status OUT NOCOPY VARCHAR2
175 
172 		   )
173   IS
174     index1 VARCHAR2(250) := 'CS_KB_SOLN_CAT_TL_N1';
176   BEGIN
177     x_return_status := fnd_api.G_RET_STS_SUCCESS;
178     SAVEPOINT populate_soln_cat_index_SAV;
179     UPDATE /*+ parallel(t) */ cs_kb_soln_categories_tl t
180     SET t.name = t.name;
181 
182     COMMIT;
183 
184     -- reestablish savepoint after commit.
185     SAVEPOINT populate_soln_cat_index_SAV;
186 
187     -- Start index synchronization
188     Sync_index( index1, 'S', 0 );
189 
190   EXCEPTION
191     WHEN OTHERS  THEN
192       ROLLBACK TO populate_soln_cat_index_SAV;
193       x_msg_error := 'populate_sol_cat_index: '
194 	  ||fnd_message.GET_STRING('CS','CS_KB_C_UNEXP_ERR')||' '||SQLERRM;
195       x_return_status := fnd_api.G_RET_STS_ERROR;
196   END populate_soln_cat_index;
197 
198 
199   /*
200    *   Populate forum index.
201    *
202    */
203   PROCEDURE populate_forum_index (
204 	        x_msg_error     OUT NOCOPY VARCHAR2,
205                 x_return_status OUT NOCOPY VARCHAR2
206 		   )
207   IS
208     index3 VARCHAR2(250) := 'CS_FORUM_MESSAGES_TL_N4';
209   BEGIN
210     x_return_status := fnd_api.G_RET_STS_SUCCESS;
211 
212     SAVEPOINT populate_forum_index_SAV;
213 
214     UPDATE /*+ parallel(t) */ cs_forum_messages_tl t
215     SET t.composite_assoc_col = 'B';
216 
217     COMMIT;
218 
219     -- reestablish savepoint after commit
220     SAVEPOINT populate_forum_index_SAV;
221 
222      -- Start index synchronization
223      Sync_index( index3, 'S', 0 );
224   EXCEPTION
225     WHEN OTHERS  THEN
226       ROLLBACK TO populate_forum_index_SAV;
227       x_msg_error := 'populate_forum_index: '
228 	  ||fnd_message.GET_STRING('CS','CS_KB_C_UNEXP_ERR')||' '||SQLERRM;
229       x_return_status := fnd_api.G_RET_STS_ERROR;
230   END populate_forum_index;
231  -- 4321268_new_apis_eof
232   /*
233    *  get_max_parallel_worker: get THE job_queue_processes value.
234    */
235   FUNCTION get_max_parallel_worker RETURN NUMBER
236    IS
237      l_worker NUMBER := 0;
238 
239      -- 4321268
240      -- Fetch the correct paremeters to calculate max. parallel workers.
241      CURSOR get_param_value(p_name IN varchar2) IS
242      SELECT to_number(nvl(VALUE, 0))
243      FROM v$parameter
244      WHERE name = lower(p_name);
245 
246      l_cpu_count NUMBER;
247      l_thread_per_cpu NUMBER;
248      -- 4321268_eof
249   BEGIN
250   --4321268
251     OPEN get_param_value('cpu_count');
252     FETCH get_param_value INTO l_cpu_Count;
253     CLOSE get_param_value;
254 
255     OPEN get_param_value('parallel_threads_per_cpu');
256     FETCH get_param_value INTO l_thread_per_cpu;
257     CLOSE get_param_value;
258 
259    --  SELECT to_number(nvl(VALUE, 0)) INTO  l_worker FROM v$parameter
260    --  WHERE NAME = 'job_queue_processes';
261     l_worker := l_cpu_count * l_thread_per_cpu;
262   --4321268
263      RETURN l_worker;
264   EXCEPTION
265     WHEN OTHERS THEN
266       RETURN l_worker;
267   END;
268 
269   /*
270    *  is_validate_mode: VALIDATE a synchronization MODE.
271    *  RETURN 'Y' IF THE MODE IS valid. Otherwise RETURN 'N'.
272    */
273   FUNCTION is_validate_mode(bmode IN VARCHAR2) RETURN VARCHAR
274    IS
275      l_valid_mode VARCHAR2(1)  := 'Y';
276      l_mode       VARCHAR2(10) := bmode;
277   BEGIN
278     IF l_mode NOT IN ('S', 'R', 'OFAST', 'OFULL', 'RC', 'DR' ) THEN
279       l_valid_mode := 'N';
280     END IF;
281     RETURN l_valid_mode;
282 
283   END;
284 
285  	/*
286    * do_create
287    *   This PROCEDURE executes THE CREATE command.
288    */
289   PROCEDURE do_create ( p_create_cmd    IN VARCHAR2,
290 		        p_index_name    IN VARCHAR2,
291 		        p_index_version IN VARCHAR2,
292 			x_msg_error     OUT NOCOPY VARCHAR2,
293 			x_return_status OUT NOCOPY VARCHAR2
294 		   )
295   IS
296 
297    l_update VARCHAR2(1) := 'Y';
298   BEGIN
299      -- initialize return status
300      x_return_status := fnd_api.G_RET_STS_ERROR;
301 
302      EXECUTE IMMEDIATE p_create_cmd;
303 
304      x_return_status := fnd_api.G_RET_STS_SUCCESS;
305   EXCEPTION
306     WHEN OTHERS  THEN
307       x_msg_error := 'do_create: '||p_index_name||' :'
308 	||fnd_message.GET_STRING('CS','CS_KB_C_UNEXP_ERR')||' '||SQLERRM;
309       x_return_status := fnd_api.G_RET_STS_ERROR;
310   END do_create;
311 
312 
313   /*
314    * resolve_parallel_indexing
315    */
316   FUNCTION resolve_parallel_indexing (
317                p_create_cmd    IN VARCHAR2,
318 	       p_worker        IN NUMBER DEFAULT 0
319                ) RETURN VARCHAR
320   IS
321      l_cmd VARCHAR2(500) := p_create_cmd;
322      l_worker        NUMBER       := p_worker;
323      l_max_worker    NUMBER       := get_max_parallel_worker;
324 
325      --3576867
326      l_db_version NUMBER := null;
327      l_compatibility VARCHAR2(100) := null;
328      l_db_version_str VARCHAR2(100) := null;
329   BEGIN
330     --3576867
331     If p_worker is null Then
332       l_worker := 0;
333     End If;
334 
335     DBMS_UTILITY.db_version(l_db_version_str, l_compatibility);
336     If l_db_version_str is null Then
337         l_db_version := 8;
338     Else
339      l_db_version := to_number(substr(l_db_version_str, 1,
340                                      (instr(l_db_version_str, '.'))-1));
341     End If;
342 
343     If l_db_version Is Not Null Then
344       If l_db_version > 8 Then
345        IF l_worker > l_max_worker THEN
346    	   l_worker := l_max_worker;
347      	END IF;
348       End if; -- l_db_version eof
349     Else
350       l_worker := 0;
351     End If;
352     -- 3576867 eof
353 
354     IF l_worker > 0 THEN
355       l_cmd := l_cmd || ' parallel '||TO_CHAR(l_worker);
356     END IF;
357 
358     RETURN l_cmd;
359   EXCEPTION
360      WHEN OTHERS  THEN
361       -- any errors: do not append anything.
362       RETURN p_create_cmd;
363   END resolve_parallel_indexing;
364 
365   -- ************************
366   --  PUBLIC IMPLEMENTATIONS
367   -- ************************
368 
369   PROCEDURE Sync_index( index1   IN VARCHAR2,
370                         bmode    IN VARCHAR2,
371                         pworker  IN NUMBER DEFAULT 0)
372   IS
373     l_index_name VARCHAR2(300) := g_cs_short_name||'.'||index1;
374 
375   BEGIN
376     IF bmode = 'S' THEN
377       AD_CTX_DDL.sync_index( l_index_name );
378     ELSIF bmode = 'OFAST' THEN
379       AD_CTX_DDL.OPTIMIZE_INDEX( l_index_name, CTX_DDL.OPTLEVEL_FAST, NULL, NULL );
380     ELSIF bmode = 'OFULL' THEN
381       AD_CTX_DDL.OPTIMIZE_INDEX( l_index_name, CTX_DDL.OPTLEVEL_FULL, NULL, NULL );
382     ELSIF bmode = 'R' THEN
383      --  4321268: rebuild in parallel mode always. Serial online mode,
384      --           is taking care in the individual index program.
385       IF pworker IS NOT NULL AND pworker > 0 THEN
386 
387         EXECUTE IMMEDIATE 'alter index ' || l_index_name ||' REBUILD parallel '|| to_char(pworker);
388       END IF;
389      -- 4321268_eof
390     ELSIF bmode = 'DR' THEN
391       -- logic to drop or create is taken in the individual api.
392       NULL;
393     ELSE
394       FND_FILE.PUT_LINE(FND_FILE.LOG,
395     		fnd_message.get_string('CS', 'CS_KB_SYN_INDEX_INV_MODE'));
396       RAISE invalid_mode_error;
397     END IF;
398   END Sync_index;
399 
400 
401   /*
402    * Sync_All_index: synchronize ALL KM indices IN serial MODE.
403    * Deprecated since 11.5.10.
404    */
405   PROCEDURE Sync_All_Index  (ERRBUF OUT NOCOPY VARCHAR2,
406                              RETCODE OUT NOCOPY NUMBER,
407                              BMODE IN VARCHAR2 DEFAULT NULL)
408   IS
409   BEGIN
410 
411      -- Return successfully
412     errbuf := fnd_message.get_string('CS', 'CS_KB_C_SUCCESS');
413     retcode :=0;
414   END Sync_All_Index;
415 
416    /*
417    * Create_Set_Index
418    *   This PROCEDURE creates THE solution INDEX AND also populates THE INDEX
419    *   content.
420    */
421   PROCEDURE Create_Set_Index
422   (  pworker IN NUMBER DEFAULT  0,
423      x_msg_error     OUT NOCOPY VARCHAR2,
424      x_return_status OUT NOCOPY VARCHAR2
425   )
426   IS
427      l_create_cmmd VARCHAR2(500):= NULL;
428       l_create_cmmd1 VARCHAR2(500):= NULL; --12.1.3
429      l_index_version VARCHAR2(15) := '115.10.1';
430      l_index_name    VARCHAR2(30) := 'cs_kb_sets_tl_N3';
431      l_index_name1    VARCHAR2(30) := 'cs_kb_sets_attach_tl_N3';
432      l_dummy_col  VARCHAR2(100):='.cs_kb_sets_tl(composite_assoc_index) '; --12.1.3
433      l_datastore VARCHAR2(100):= '.CS_KB_COMPOSITE_ELES '; --12.1.3
434 
435   BEGIN
436 
437 
438    l_create_cmmd :=
439         ' CREATE INDEX '||g_cs_short_name||'.'||l_index_name||' on '
440      || g_cs_short_name||'.cs_kb_sets_tl(composite_assoc_index) '
441      || ' INDEXTYPE IS ctxsys.context '
442      || ' parameters (''datastore '||g_apps_short_name||'.CS_KB_COMPOSITE_ELES '
443      || ' section group '||g_apps_short_name||'.CS_KB_BASIC_GRP '
444      || ' lexer  '||g_apps_short_name||'.CS_KB_GLOBAL_LEXER language column SOURCE_LANG '
445      || ' wordlist '||g_apps_short_name||'.CS_KB_FUZZY_PREF '
446      --4321268
447      || ' storage ' ||g_apps_short_name||'.CS_KB_INDEX_STORAGE '; -- <-command not yet completed
448      -- 4321268_eof
449      -- Start 12.1.3
450           IF FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL THEN
451        FND_LOG.STRING(FND_LOG.LEVEL_STATEMENT, 'csk.plsql.cs_kb_conc_prog_pkg.Create_Set_Index',
452                      ' attachment_flag:'||attachment_flag);
453     END IF;
454 
455 /* l_create_cmmd :=
456         ' CREATE INDEX '||g_cs_short_name||'.'||l_index_name||' on '
457      || g_cs_short_name||l_dummy_col
458      || ' INDEXTYPE IS ctxsys.context '
459      || ' parameters (''datastore '||g_apps_short_name||l_datastore
460      || ' section group '||g_apps_short_name||'.CS_KB_BASIC_GRP '
461      || ' lexer  '||g_apps_short_name||'.CS_KB_GLOBAL_LEXER language column SOURCE_LANG '
462      || ' wordlist '||g_apps_short_name||'.CS_KB_FUZZY_PREF '
463      --4321268
464      || ' storage ' ||g_apps_short_name||'.CS_KB_INDEX_STORAGE '; -- <-command not yet completed
465      -- 4321268_eof*/
466 
467    IF attachment_flag = 'Y' THEN
468     -- l_index_name := 'cs_kb_sets_attach_tl_N3';
469       l_dummy_col :='.cs_kb_sets_tl(composite_assoc_attach_index) ';
470      l_datastore := '.CS_KB_COMPOSITE_ATTACH_ELES ';
471       l_create_cmmd1 :=
472         ' CREATE INDEX '||g_cs_short_name||'.'||l_index_name1||' on '
473      || g_cs_short_name||l_dummy_col
474      || ' INDEXTYPE IS ctxsys.context '
475      || ' parameters (''datastore '||g_apps_short_name||l_datastore
476      || ' section group '||g_apps_short_name||'.CS_KB_BASIC_GRP '
477      || ' lexer  '||g_apps_short_name||'.CS_KB_GLOBAL_LEXER language column SOURCE_LANG '
478      || ' wordlist '||g_apps_short_name||'.CS_KB_FUZZY_PREF '
479      --4321268
480      || ' storage ' ||g_apps_short_name||'.CS_KB_INDEX_STORAGE '; -- <-command not yet completed
481      -- 4321268_eof
482    END IF;
483 
484       IF FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL THEN
485        FND_LOG.STRING(FND_LOG.LEVEL_STATEMENT, 'csk.plsql.cs_kb_conc_prog_pkg.Create_Set_Index',
486                      'l_index_name:'||l_index_name||  'l_dummy_col:'||l_dummy_col||  'l_datastore:'||l_datastore);
487     END IF;
488 
489            IF FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL THEN
490        FND_LOG.STRING(FND_LOG.LEVEL_STATEMENT, 'csk.plsql.cs_kb_conc_prog_pkg.Create_Set_Index',
491                      ' l_create_cmmd:'|| l_create_cmmd);
492     END IF;
493 
494       -- End 12.1.3
495      x_return_status := fnd_api.G_RET_STS_ERROR;
496 
497      -- 4321268
498      IF  nvl(pworker,0) = 0 THEN
499         -- Create index online
500         -- 1. Create index without populate
501         l_create_cmmd := l_create_cmmd || ' nopopulate '') ';
502 	l_create_cmmd1 := l_create_cmmd1 || ' nopopulate '') ';  --12.1.3
503 
504      ELSE
505          l_create_cmmd := l_create_cmmd || ''')';
506      l_create_cmmd := resolve_parallel_indexing(l_create_cmmd, pworker);
507      --12.1.3
508       l_create_cmmd1 := l_create_cmmd1 || ''')';
509      l_create_cmmd1 := resolve_parallel_indexing(l_create_cmmd1, pworker);
510      --12.1.3
511      END IF;
512            IF FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL THEN
513        FND_LOG.STRING(FND_LOG.LEVEL_STATEMENT, 'csk.plsql.cs_kb_conc_prog_pkg.Create_Set_Index',
514                      ' l_create_cmmd before do_create:'|| l_create_cmmd);
515     END IF;
516 
517      -- 4321268_eof
518 
519      do_create(
520        p_create_cmd    => l_create_cmmd,
521        p_index_name    => l_index_name,
522        p_index_version => l_index_version,
523        x_msg_error     => x_msg_error,
524        x_return_status => x_return_status );
525 	--12.1.3
526       IF attachment_flag = 'Y' THEN
527 	IF FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL THEN
528 	   FND_LOG.STRING(FND_LOG.LEVEL_STATEMENT, 'csk.plsql.cs_kb_conc_prog_pkg.Create_Set_Index',
529            ' l_create_cmmd inside do_create:'|| l_create_cmmd1 ||l_index_name1);
530 	END IF;
531 
532 
533       do_create(
534        p_create_cmd    => l_create_cmmd1,
535        p_index_name    => l_index_name1,
536        p_index_version => l_index_version,
537        x_msg_error     => x_msg_error,
538        x_return_status => x_return_status );
539      END IF;
540      IF x_return_status <> fnd_api.G_RET_STS_SUCCESS THEN
541      	RAISE create_index_error;
542      END IF;
543 
544      -- 4321268
545      IF nvl(pworker, 0) = 0 THEN
546              populate_set_index (
547 		   x_msg_error ,
548                    x_return_status
549 	);
550      END IF;
551      IF x_return_status <> fnd_api.G_RET_STS_SUCCESS THEN
552      	RAISE create_index_error;
553      END IF;
554       -- 4321268_eof
555 
556 
557      x_return_status := fnd_api.G_RET_STS_SUCCESS;
558 
559   EXCEPTION
560     WHEN create_index_error THEN
561   		 NULL;  -- x_msg_error is set in the do_create api.
562     WHEN others THEN
563       x_msg_error := 'Create_Set_Index: '
564        ||fnd_message.GET_STRING('CS','CS_KB_C_UNEXP_ERR')||' '||SQLERRM;
565   END Create_Set_Index;
566 
567 
568   /*
569    * Create_Element_Index
570    *   This PROCEDURE creates THE STATEMENT INDEX AND also populates THE INDEX
571    *   content.
572    */
573   PROCEDURE Create_Element_Index
574   (  pworker IN NUMBER DEFAULT  0,
575      x_msg_error     OUT NOCOPY VARCHAR2,
576      x_return_status OUT NOCOPY VARCHAR2
577   )
578   IS
579      l_create_cmmd VARCHAR2(500):= NULL;
580 
581      l_index_version VARCHAR2(15) := '115.10.1';
582      l_index_name    VARCHAR2(30) := 'cs_kb_elements_tl_N2';
583   BEGIN
584     l_create_cmmd :=
585         ' CREATE INDEX '||g_cs_short_name||'.cs_kb_elements_tl_N2 on '
586       ||g_cs_short_name||'.cs_kb_elements_tl(composite_text_index) '
587       ||' INDEXTYPE IS ctxsys.context '
588       ||' parameters (''datastore '||g_apps_short_name||'.CS_KB_ELES '
589       ||' section group '||g_apps_short_name||'.CS_KB_BASIC_GRP '
590       ||' lexer '||g_apps_short_name||'.CS_KB_GLOBAL_LEXER language column SOURCE_LANG '
591       ||' wordlist '||g_apps_short_name||'.CS_KB_FUZZY_PREF '
592       --4321268
593       || ' storage ' ||g_apps_short_name||'.CS_KB_INDEX_STORAGE '; -- <-command not yet completed
594       -- 4321268_eof
595 
596      x_return_status := fnd_api.G_RET_STS_ERROR;
597 
598      -- 4321268
599      IF  nvl(pworker,0) = 0 THEN
600         -- Create index online
601         -- 1. Create index without populate
602         l_create_cmmd := l_create_cmmd || ' nopopulate '') ';
603      ELSE
604          l_create_cmmd := l_create_cmmd || ''')';
605      l_create_cmmd := resolve_parallel_indexing(l_create_cmmd, pworker);
606 
607      END IF;
608      -- 4321268_eof
609 
610       do_create
611         (  p_create_cmd    => l_create_cmmd,
612            p_index_name    => l_index_name,
613 	   p_index_version => l_index_version,
614 	   x_msg_error     => x_msg_error,
615 	   x_return_status => x_return_status
616 	);
617 
618      -- 4321268
619      IF nvl(pworker, 0) = 0 THEN
620              populate_element_index (
621 		 x_msg_error ,
622                  x_return_status
623 		   );
624      END IF;
625      IF x_return_status <> fnd_api.G_RET_STS_SUCCESS THEN
626      	RAISE create_index_error;
627      END IF;
628       -- 4321268_eof
629 
630      IF x_return_status <> fnd_api.G_RET_STS_SUCCESS THEN
631      	RAISE create_index_error;
632      END IF;
633      x_return_status := fnd_api.G_RET_STS_SUCCESS;
634 
635   EXCEPTION
636     WHEN create_index_error THEN
637       NULL;  -- x_msg_error is set in the do_create api.
638     WHEN others THEN
639       x_msg_error := 'Create_Element_Index: '
640         ||fnd_message.GET_STRING('CS','CS_KB_C_UNEXP_ERR')||' '||SQLERRM;
641   END Create_Element_Index;
642 
643 
644   /*
645    * Create_Soln_Cat_Index
646    *   This PROCEDURE creates THE CATEGORY INDEX AND also populates THE INDEX
647    *   content.
648    */
649   PROCEDURE Create_Soln_Cat_Index
650   (  pworker IN NUMBER DEFAULT  0,
651      x_msg_error     OUT NOCOPY VARCHAR2,
652      x_return_status OUT NOCOPY VARCHAR2
653   )
654   IS
655      l_create_cmmd VARCHAR2(500):= NULL;
656      l_index_version VARCHAR2(15) := '115.10.1';
657      l_index_name    VARCHAR2(30) := 'CS_KB_SOLN_CAT_TL_N1';
658 
659   BEGIN
660     l_create_cmmd :=
661           ' CREATE INDEX '||g_cs_short_name||'.CS_KB_SOLN_CAT_TL_N1 on '
662         ||g_cs_short_name||'.cs_kb_soln_categories_tl(name) '
663         ||' INDEXTYPE IS ctxsys.context '
664         ||' parameters ('' '
665         ||' lexer '||g_apps_short_name||'.CS_KB_GLOBAL_LEXER language column SOURCE_LANG '
669         -- 4321268_eof
666         ||' wordlist '||g_apps_short_name||'.CS_KB_FUZZY_PREF '
667         --4321268
668         || ' storage ' ||g_apps_short_name||'.CS_KB_INDEX_STORAGE '; -- <-command not yet completed
670 
671       x_return_status := fnd_api.G_RET_STS_ERROR;
672 
673       -- 4321268
674       IF  nvl(pworker,0) = 0 THEN
675         -- Create index online
676         -- 1. Create index without populate
677          l_create_cmmd := l_create_cmmd || ' nopopulate '') ';
678       ELSE
679 
680          l_create_cmmd := l_create_cmmd || ''')';
681       l_create_cmmd := resolve_parallel_indexing(l_create_cmmd, pworker);
682 
683       END IF;
684       -- 4321268_eof
685 
686       do_create
687       (  p_create_cmd    => l_create_cmmd,
688          p_index_name    => l_index_name,
689 	 p_index_version => l_index_version,
690 	 x_msg_error     => x_msg_error,
691 	 x_return_status => x_return_status
692        );
693 
694      -- 4321268
695      IF nvl(pworker, 0) = 0 THEN
696              populate_soln_cat_index (
697 	           x_msg_error ,
698 		   x_return_status
699 		   );
700      END IF;
701      IF x_return_status <> fnd_api.G_RET_STS_SUCCESS THEN
702      	RAISE create_index_error;
703      END IF;
704      -- 4321268_eof
705      x_return_status := fnd_api.G_RET_STS_SUCCESS;
706 
707   EXCEPTION
708     WHEN create_index_error THEN
709   		 NULL;  -- x_msg_error is set in the do_create api.
710     WHEN others THEN
711       x_msg_error := 'Create_Element_Index: '
712         ||fnd_message.GET_STRING('CS','CS_KB_C_UNEXP_ERR')||' '||SQLERRM;
713   END Create_Soln_Cat_Index;
714 
715    /*
716    * Create_Forum_Index
717    *   This PROCEDURE creates THE forum INDEX AND also populates THE INDEX
718    *   content.
719    */
720   PROCEDURE Create_Forum_Index
721   (  pworker IN NUMBER DEFAULT  0,
722      x_msg_error     OUT NOCOPY VARCHAR2,
723      x_return_status OUT NOCOPY VARCHAR2
724   )
725   IS
726      l_create_cmmd VARCHAR2(500):= NULL;
727 
728      l_index_version VARCHAR2(15) := '115.10.1';
729      l_index_name    VARCHAR2(30) := 'cs_forum_messages_tl_n4';
730   BEGIN
731     l_create_cmmd :=
732          'create index '||g_cs_short_name||'.cs_forum_messages_tl_n4 '
733       || 'on '||g_cs_short_name||'.cs_forum_messages_tl(composite_assoc_col) '
734       || 'indextype is ctxsys.context parameters( '''
735       || 'datastore '||g_apps_short_name||'.CS_FORUM_MESG_ELES '
736       || ' section group '||g_apps_short_name||'.CS_KB_BASIC_GRP '
737       || 'lexer '||g_apps_short_name||'.CS_KB_GLOBAL_LEXER language column SOURCE_LANG '
738       || 'wordlist '||g_apps_short_name||'.CS_KB_FUZZY_PREF '
739       --4321268
740       || ' storage ' ||g_apps_short_name||'.CS_KB_INDEX_STORAGE '; -- <-command not yet completed
741       -- 4321268_eof
742 
743      x_return_status := fnd_api.G_RET_STS_ERROR;
744 
745      -- 4321268
746      IF  nvl(pworker,0) = 0 THEN
747         -- Create index online
748         -- 1. Create index without populate
749         l_create_cmmd := l_create_cmmd || ' nopopulate '') ';
750      ELSE
751          l_create_cmmd := l_create_cmmd || ''')';
752      l_create_cmmd := resolve_parallel_indexing(l_create_cmmd, pworker);
753 
754      END IF;
755      -- 4321268_eof
756 
757       do_create
758         (  p_create_cmd    => l_create_cmmd,
759            p_index_name    => l_index_name,
760            p_index_version => l_index_version,
761            x_msg_error     => x_msg_error,
762            x_return_status => x_return_status
763          );
764 
765      -- 4321268
766      IF nvl(pworker, 0) = 0 THEN
767              populate_forum_index (
768                      x_msg_error ,
769 		     x_return_status
770 		   );
771      END IF;
772      IF x_return_status <> fnd_api.G_RET_STS_SUCCESS THEN
773      	RAISE create_index_error;
774      END IF;
775       -- 4321268_eof
776      x_return_status := fnd_api.G_RET_STS_SUCCESS;
777 
778   EXCEPTION
779     WHEN create_index_error THEN
780       NULL;  -- x_msg_error is set in the do_create api.
781     WHEN others THEN
782       x_msg_error := 'Create_Forum_Index: '
783             ||fnd_message.GET_STRING('CS','CS_KB_C_UNEXP_ERR')||' '||SQLERRM;
784   END Create_Forum_Index;
785 
786 
787 
788   PROCEDURE Drop_Index
789   ( p_index_name IN VARCHAR,
790     x_msg_error     OUT NOCOPY VARCHAR2,
791     x_return_status OUT NOCOPY VARCHAR2
792     )
793   IS
794      drop_index VARCHAR2(100) := NULL;
795 
796      CURSOR get_index_cursor(p_index_name VARCHAR2, p_owner VARCHAR2) IS
797        SELECT COUNT(*) FROM dba_indexes
798        WHERE index_name = UPPER(p_index_name)
799        AND owner= UPPER(p_owner);
800 
801      l_total NUMBER := 0;
802 
803   BEGIN
804     x_return_status := fnd_api.G_RET_STS_ERROR;
805     IF  p_index_name IS NULL THEN
806        RETURN;
807     END IF;
808 
809     -- If only if the index exists:
810     OPEN get_index_cursor(p_index_name, g_cs_short_name);
811     FETCH get_index_cursor INTO l_total;
812     CLOSE get_index_cursor;
813 
814     IF l_total > 0 THEN
815       drop_index := 'drop index '||g_cs_short_name||'.'||p_index_name||' force ';
816       EXECUTE IMMEDIATE drop_index;
817     END IF;
818 
819     x_return_status := fnd_api.G_RET_STS_SUCCESS;
820 
821     -- Logic to remove the index version in the
822     -- global system table.
823   EXCEPTION
824     WHEN others THEN
825       x_msg_error := 'Drop_Index: '||
826                  fnd_message.GET_STRING('CS','CS_KB_C_UNEXP_ERR')||' '||
827                  SQLERRM;
828   END Drop_Index;
829 
830 
831   /*
832    * Sync_Set_Index
833    *   This PROCEDURE syncs THE Oracle Text INDEX FOR KM Solutions TO
834    *   bring THE INDEX up-TO-DATE.
835    */
836   PROCEDURE Sync_Set_Index
837   (  errbuf OUT NOCOPY VARCHAR2,
838      retcode OUT NOCOPY NUMBER,
839      bmode   IN VARCHAR2,
840      pworker IN NUMBER DEFAULT  0,
841      attachment IN VARCHAR2)
842   IS
843     CURSOR delay_marked_solns_batch_csr( c_batch_size NUMBER ) IS
844       SELECT set_id
845       FROM cs_kb_sets_b
846      -- 3679483
847        -- WHERE reindex_flag = 'Y'
848       WHERE reindex_flag = 'U'
849      -- 3679483 eof
850       AND ROWNUM <= c_batch_size;
851 
852     l_solution_id NUMBER := 0;
853 
854     l_soln_comp_index VARCHAR2(250) := 'CS_KB_SETS_TL_N3';
855      l_soln_comp_attach_index VARCHAR2(250):= 'CS_KB_SETS_ATTACH_TL_N3'; --12.1.3
856     l_num_batch_rows_updated NUMBER := 0;
857     l_reindex_batch_size NUMBER := 300;
861   BEGIN
858     l_mode VARCHAR2(10) := bmode;
859 
860     l_return_status VARCHAR2(1) :=  fnd_api.G_RET_STS_ERROR;
862       IF FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL THEN
863        FND_LOG.STRING(FND_LOG.LEVEL_STATEMENT, 'csk.plsql.cs_kb_conc_prog_pkg.Sync_Set_Index',
864                      'Index attachments:'||attachment);
865     END IF;
866     --12.1.3
867    --Commented to fix bug 8757484
868    --IF attachment = 'Y' THEN
869       attachment_flag :='Y';
870    --END IF;
871       IF FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL THEN
872        FND_LOG.STRING(FND_LOG.LEVEL_STATEMENT, 'csk.plsql.cs_kb_conc_prog_pkg.Sync_Set_Index',
873                      'l_soln_comp_index:'||l_soln_comp_index);
874     END IF;
875 
876     IF FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL THEN
877        FND_LOG.STRING(FND_LOG.LEVEL_STATEMENT, 'csk.plsql.cs_kb_conc_prog_pkg.Sync_Set_Index',
878                      'l_soln_comp_attach_index:'||l_soln_comp_attach_index);
879     END IF;
880 
881    --12.1.3
882     -- Initialize some variables
883     retcode := 2; -- init return val to FAIL
884 
885     IF l_mode IS NULL THEN
886       l_mode := 'S';
887     END IF;
888 
889     IF is_validate_mode(l_mode) = 'N' THEN
890      RAISE invalid_mode_error;
891    END IF;
892 
893      -- check whether it is 'DR'
894      IF l_mode = 'DR' THEN
895        -- At this point we can assume that we can safely drop the index.
896         Drop_Index(l_soln_comp_index,
897                    errbuf,
898                    l_return_status);
899 	--12.1.3
900 	--IF attachment = 'Y' THEN
901 		Drop_Index(l_soln_comp_attach_index,
902                    errbuf,
903                    l_return_status);
904 	--END IF;
905 	--12.1.3
906         IF l_return_status <> fnd_api.G_RET_STS_SUCCESS THEN
907           RAISE drop_index_error;
908         END IF;
909 
910         Create_Set_Index(pworker,
911                          errbuf,
912                          l_return_status);
913         IF l_return_status <> fnd_api.G_RET_STS_SUCCESS THEN
914           RAISE create_index_error;
915         END IF;
916      ELSIF l_mode = 'RC' THEN
917        -- Rebuild content cache
918         Rebuild_Soln_Content_Cache( errbuf, retcode );
919         IF retcode <> 0 THEN
920           RAISE rebuild_cache_error;
921         END IF;
922      ELSE
923       fnd_profile.get('CS_KB_REINDEX_BATCH_SIZE', l_reindex_batch_size);
924       IF ( l_reindex_batch_size IS NULL ) THEN
925         l_reindex_batch_size := 300;
926       END IF;
927 
928       -- Sync the composite solution index up-front.
929       -- This will bring any solutions already marked for reindexing
930       -- up-to date and make them searchable.
931       -- 4321268
932       IF (pworker IS NULL OR pworker = 0) AND l_mode = 'R' THEN
933          populate_set_index (
934 			    x_msg_error      => errbuf,
935 		     	x_return_status  => l_return_status
936 		   );
937       Else
938       Sync_index( l_soln_comp_index, l_mode, PWORKER );
939       --12.1.3
940 	--IF attachment = 'Y' THEN
941 		 Sync_index( l_soln_comp_attach_index, l_mode, PWORKER );
942 	--END IF;
943 	--12.1.3
944       END IF;
945       -- 4321268_eof
946 
947       -- Query up solutions that have been delay-marked for reindexing.
948       -- Loop through these solutions in batches (batch size defined by
949       -- profile option) and transfer the delay-mark to immediate mark.
950       -- After the mark transfer for each of these batches, sync the index
951       -- to make the batch of solutions searchable.
952       LOOP
953         l_num_batch_rows_updated := 0;
954 
955         OPEN delay_marked_solns_batch_csr( l_reindex_batch_size );
956         LOOP
957           FETCH delay_marked_solns_batch_csr INTO l_solution_id;
958           -- Exit inner loop when there are no more delay-marked
959           -- statements in the batch
960           EXIT WHEN delay_marked_solns_batch_csr%NOTFOUND;
961 
962          -- Immediately mark the solution composite text index column
963 	 /* Commented for 12.1.3
964           UPDATE cs_kb_sets_tl
965           SET composite_assoc_index = 'U'
966           WHERE set_id = l_solution_id;*/
967 	   --12.1.3
968 	  --IF attachment = 'Y' THEN
969 		UPDATE cs_kb_sets_tl
970 		SET composite_assoc_attach_index = 'U'
971 		WHERE set_id = l_solution_id;
972 	  --ELSE
973 		UPDATE cs_kb_sets_tl
974 		SET composite_assoc_index = 'U'
975 		WHERE set_id = l_solution_id;
976          --END IF;
977 	  --12.1.3
978 
979           -- Clear the delayed index mark on the solution
980           UPDATE cs_kb_sets_b
981           SET reindex_flag = NULL
982           WHERE set_id = l_solution_id;
983 
984           l_num_batch_rows_updated := l_num_batch_rows_updated + 1;
985         END LOOP;
986         CLOSE delay_marked_solns_batch_csr;
987         COMMIT;
988 
989         -- Exit outer loop when there are no more rows to update
990         EXIT WHEN l_num_batch_rows_updated = 0;
991 
992         -- Otherwise sync the index and loop again for the next batch
993         Sync_index( l_soln_comp_index, l_mode, PWORKER );
994 
995       END LOOP;
996     END IF; -- l_mode check
997 
998     -- klou (SRCHEFF)
999     -- Update magic word.
1000     Update_Magic_Word;
1001 
1002     -- Set return value and log message to Success
1003     errbuf := fnd_message.get_string('CS', 'CS_KB_C_SUCCESS');
1004     retcode := 0;
1005 
1006   EXCEPTION
1007     WHEN invalid_mode_error THEN
1008       BEGIN
1012       BEGIN
1009         errbuf := fnd_message.get_string('CS', 'CS_KB_SYN_INDEX_INV_MODE');
1010       END;
1011     WHEN drop_index_error THEN
1013         FND_FILE.PUT_LINE(FND_FILE.LOG, errbuf);
1014       EXCEPTION
1015         WHEN others THEN
1016           NULL;
1017       END;
1018     WHEN create_index_error THEN
1019       BEGIN
1020         FND_FILE.PUT_LINE(FND_FILE.LOG, errbuf);
1021       EXCEPTION
1022         WHEN others THEN
1023           NULL;
1024       END;
1025     WHEN others THEN
1026       errbuf := 'Sync_Set_Index: '||
1027              fnd_message.GET_STRING('CS','CS_KB_C_UNEXP_ERR')||' '||
1028              SQLERRM;
1029       -- Write out error to concurrent program log
1030       BEGIN
1031         FND_FILE.PUT_LINE(FND_FILE.LOG, errbuf);
1032       EXCEPTION
1033         WHEN others THEN
1034           NULL;
1035       END;
1036 
1037   END Sync_Set_Index;
1038 
1039 
1040 
1041   /*
1042    * Sync_Element_Index
1043    *   This PROCEDURE syncs THE Oracle Text INDEX FOR KM Statements TO
1044    *   bring THE INDEX up-TO-DATE.
1045    */
1046   PROCEDURE Sync_Element_Index
1047   ( ERRBUF OUT NOCOPY VARCHAR2,
1048     RETCODE OUT NOCOPY NUMBER,
1049     BMODE IN VARCHAR2,
1050     pworker  IN NUMBER DEFAULT 0)
1051   IS
1052     CURSOR delay_marked_stmts_batch_csr( c_batch_size NUMBER ) IS
1053       SELECT element_id
1054       FROM cs_kb_elements_b
1055       -- 3679483
1056       -- WHERE reindex_flag = 'Y'
1057       WHERE reindex_flag = 'U'
1058       -- 3679483 eof
1059       AND ROWNUM <= c_batch_size;
1060 
1061     l_statement_id NUMBER := 0;
1062     l_statement_comp_index VARCHAR2(250) := 'CS_KB_ELEMENTS_TL_N2';
1063     l_num_batch_rows_updated NUMBER := 0;
1064     l_reindex_batch_size NUMBER := 300;
1065     l_mode   VARCHAR2(10) := bmode;
1066     l_return_status VARCHAR2(1) :=  fnd_api.G_RET_STS_ERROR;
1067   BEGIN
1068     -- Initialize some variables
1069     retcode := 2; -- init return val to FAIL
1070 
1071     IF l_mode IS NULL THEN
1072       l_mode := 'S';
1073     END IF;
1074 
1075     IF is_validate_mode(l_mode) = 'N' THEN
1076      RAISE invalid_mode_error;
1077     END IF;
1078 
1079      -- check whether it is 'DR'
1080      IF l_mode = 'DR' THEN
1081        -- At this point we can assume that we can safely drop the index.
1082         Drop_Index(l_statement_comp_index,
1083                    errbuf,
1084                    l_return_status);
1085         IF l_return_status <> fnd_api.G_RET_STS_SUCCESS THEN
1086           RAISE drop_index_error;
1087         END IF;
1088 
1089         Create_Element_Index(pworker,
1090                              errbuf,
1091                              l_return_status);
1092         IF l_return_status <> fnd_api.G_RET_STS_SUCCESS THEN
1093           RAISE create_index_error;
1094         END IF;
1095      ELSE
1096         fnd_profile.get('CS_KB_REINDEX_BATCH_SIZE', l_reindex_batch_size);
1097         IF ( l_reindex_batch_size IS NULL ) THEN
1098           l_reindex_batch_size := 300;
1099         END IF;
1100 
1101         -- Sync the composite statement index up-front.
1102         -- This will bring any statement already marked for reindexing
1103         -- up-to date and make them searchable.
1104         -- 4321268
1105         IF (pworker IS NULL OR pworker = 0) AND l_mode = 'R' THEN
1106              populate_element_index (
1107     			    x_msg_error      => errbuf,
1108     		     	x_return_status  => l_return_status
1109     		   );
1110         ELSE
1111             Sync_index( l_statement_comp_index, bmode, PWORKER );
1112         END IF;
1113         -- 4321268_eof
1114         -- Query up statements that have been delay-marked for reindexing.
1115         -- Loop through these statements in batches (batch size defined by
1116         -- profile option) and transfer the delay-mark to immediate mark.
1117         -- After the mark transfer for each of these batches, sync the index
1118         -- to make the batch of statements searchable.
1119         LOOP
1120           l_num_batch_rows_updated := 0;
1121 
1122           OPEN delay_marked_stmts_batch_csr( l_reindex_batch_size );
1123           LOOP
1124             FETCH delay_marked_stmts_batch_csr INTO l_statement_id;
1125             -- Exit inner loop when there are no more delay-marked
1126             -- statements in the batch
1127             EXIT WHEN delay_marked_stmts_batch_csr%NOTFOUND;
1128 
1129             -- Immediately mark the statement composite text index column
1130             UPDATE cs_kb_elements_tl
1131             SET composite_text_index = 'U'
1132             WHERE element_id = l_statement_id;
1133 
1134             -- Clear the delayed index mark on the statement
1135             UPDATE cs_kb_elements_b
1136             SET reindex_flag = NULL
1137             WHERE element_id = l_statement_id;
1138 
1139             l_num_batch_rows_updated := l_num_batch_rows_updated + 1;
1140           END LOOP;
1141           CLOSE delay_marked_stmts_batch_csr;
1142           COMMIT;
1143 
1144           -- Exit outer loop when there are no more rows to update
1145           EXIT WHEN l_num_batch_rows_updated = 0;
1146 
1147           -- Otherwise sync the index and loop again for the next batch
1148           Sync_index( l_statement_comp_index, bmode );
1149 
1150         END LOOP;
1151       END IF;
1152     -- Set return value and log message to Success
1153     errbuf := fnd_message.get_string('CS', 'CS_KB_C_SUCCESS');
1154     retcode := 0;
1155 
1156   EXCEPTION
1157     WHEN invalid_mode_error THEN
1158       BEGIN
1162       BEGIN
1159         errbuf := fnd_message.get_string('CS', 'CS_KB_SYN_INDEX_INV_MODE');
1160       END;
1161     WHEN drop_index_error THEN
1163         FND_FILE.PUT_LINE(FND_FILE.LOG, errbuf);
1164       EXCEPTION
1165         WHEN others THEN
1166           NULL;
1167       END;
1168     WHEN create_index_error THEN
1169       BEGIN
1170         FND_FILE.PUT_LINE(FND_FILE.LOG, errbuf);
1171       EXCEPTION
1172         WHEN others THEN
1173           NULL;
1174       END;
1175     WHEN others THEN
1176       errbuf := 'Sync_Element_Index: '||
1177                fnd_message.GET_STRING('CS','CS_KB_C_UNEXP_ERR')||' '||
1178                SQLERRM;
1179       -- Write out error to concurrent program log
1180       BEGIN
1181         FND_FILE.PUT_LINE(FND_FILE.LOG, errbuf);
1182       EXCEPTION
1183         WHEN others THEN
1184           NULL;
1185       END;
1186   END Sync_Element_Index;
1187 
1188 
1189    PROCEDURE Sync_Forum_Index(ERRBUF OUT NOCOPY VARCHAR2,
1190                               RETCODE OUT NOCOPY NUMBER,
1191                               BMODE IN VARCHAR2,
1192                               pworker  IN NUMBER DEFAULT 0)
1193 
1194   IS
1195     index3 VARCHAR2(250) := 'CS_FORUM_MESSAGES_TL_N4';
1196     l_mode VARCHAR2(10) := bmode;
1197     l_return_status VARCHAR2(1) :=  fnd_api.G_RET_STS_ERROR;
1198   BEGIN
1199    -- Initialize some variables
1200    retcode := 2; -- init return val to FAIL
1201 
1202    IF l_mode IS NULL THEN
1203     l_mode := 'S';
1204    END IF;
1205 
1206    IF is_validate_mode(l_mode) = 'N' THEN
1207     RAISE invalid_mode_error;
1208    END IF;
1209 
1210     -- check whether it is 'DR'
1211     IF l_mode = 'DR' THEN
1212       -- At this point we can assume that we can safely drop the index.
1213       Drop_Index(index3,
1214                  errbuf,
1215                  l_return_status);
1216       IF l_return_status <> fnd_api.G_RET_STS_SUCCESS THEN
1217         RAISE drop_index_error;
1218       END IF;
1219 
1220       Create_Forum_Index(pworker,
1221                          errbuf,
1222                          l_return_status);
1223       IF l_return_status <> fnd_api.G_RET_STS_SUCCESS THEN
1224         RAISE create_index_error;
1225       END IF;
1226     ELSE
1227       -- 4321268
1228       IF (pworker IS NULL OR pworker = 0) AND l_mode = 'R' THEN
1229          populate_forum_index (
1230 			    x_msg_error      => errbuf,
1231 		     	x_return_status  => l_return_status
1232 		   );
1233       Else
1234           Sync_index( index3, l_mode, PWORKER );
1235       END IF;
1236       -- 4321268_eof
1237     END IF;
1238 
1239    -- Return successfully
1240    errbuf := fnd_message.get_string('CS', 'CS_KB_C_SUCCESS');
1241    retcode := 0;
1242   EXCEPTION
1243   WHEN invalid_mode_error THEN
1244     BEGIN
1245       errbuf := fnd_message.get_string('CS', 'CS_KB_SYN_INDEX_INV_MODE');
1246     END;
1247   WHEN drop_index_error THEN
1248     BEGIN
1249       FND_FILE.PUT_LINE(FND_FILE.LOG, errbuf);
1250     EXCEPTION
1251       WHEN others THEN
1252         NULL;
1253     END;
1254   WHEN create_index_error THEN
1255     BEGIN
1256       FND_FILE.PUT_LINE(FND_FILE.LOG, errbuf);
1257     EXCEPTION
1258       WHEN others THEN
1259         NULL;
1260     END;
1261   WHEN others THEN
1262       errbuf := 'Sync_Forum_Index: '||
1263               fnd_message.GET_STRING('CS','CS_KB_C_UNEXP_ERR')||' '||
1264               SQLERRM;
1265     BEGIN
1266       FND_FILE.PUT_LINE(FND_FILE.LOG, errbuf);
1267     EXCEPTION
1268       WHEN others THEN
1269         NULL;
1270     END;
1271    END Sync_Forum_Index;
1272 
1273   PROCEDURE Sync_Soln_Cat_Index(ERRBUF OUT NOCOPY VARCHAR2,
1274                                 RETCODE OUT NOCOPY NUMBER,
1275                                 BMODE IN VARCHAR2,
1276                                 pworker  IN NUMBER DEFAULT 0)
1277   IS
1278   index1 VARCHAR2(250) := 'CS_KB_SOLN_CAT_TL_N1';
1279   l_mode VARCHAR2(10) := bmode;
1283     retcode := 2;
1280   l_return_status VARCHAR2(1) :=  fnd_api.G_RET_STS_ERROR;
1281 
1282   BEGIN
1284 
1285     IF l_mode IS NULL THEN
1286       l_mode := 'S';
1287     END IF;
1288 
1289     IF is_validate_mode(l_mode) = 'N' THEN
1290      RAISE invalid_mode_error;
1291     END IF;
1292 
1293      -- check whether it is 'DR'
1294      IF l_mode = 'DR' THEN
1295        -- At this point we can assume that we can safely drop the index.
1296         Drop_Index(index1,
1297                    errbuf,
1298                    l_return_status);
1299         IF l_return_status <> fnd_api.G_RET_STS_SUCCESS THEN
1300           RAISE drop_index_error;
1301         END IF;
1302 
1303       Create_Soln_Cat_Index(pworker,
1304                             errbuf,
1305                             l_return_status);
1306       IF l_return_status <> fnd_api.G_RET_STS_SUCCESS THEN
1307         RAISE create_index_error;
1308       END IF;
1309      ELSE
1310       -- 4321268
1311       IF (pworker IS NULL OR pworker = 0) AND l_mode = 'R' THEN
1312          populate_soln_cat_index (
1313 			    x_msg_error      => errbuf,
1314 		     	x_return_status  => l_return_status
1315 		   );
1316       Else
1317           Sync_index( index1, l_mode, PWORKER );
1318       END IF;
1319       -- 4321268_eof
1320      END IF;
1321 
1322     -- Return successfully
1323     errbuf := fnd_message.get_string('CS', 'CS_KB_C_SUCCESS');
1324     retcode := 0;
1325   EXCEPTION
1326    WHEN invalid_mode_error THEN
1327     BEGIN
1328       errbuf := fnd_message.get_string('CS', 'CS_KB_SYN_INDEX_INV_MODE');
1329     END;
1330    WHEN drop_index_error THEN
1331     BEGIN
1332       FND_FILE.PUT_LINE(FND_FILE.LOG, errbuf);
1333     EXCEPTION
1334       WHEN others THEN
1335         NULL;
1336     END;
1337    WHEN create_index_error THEN
1338     BEGIN
1339       FND_FILE.PUT_LINE(FND_FILE.LOG, errbuf);
1340     EXCEPTION
1341       WHEN others THEN
1342         NULL;
1343     END;
1344     WHEN others THEN
1345     errbuf := 'Sync_Soln_Cat_Index: '||
1346               fnd_message.GET_STRING('CS','CS_KB_C_UNEXP_ERR')||' '||
1347               SQLERRM;
1348     BEGIN
1349       FND_FILE.PUT_LINE(FND_FILE.LOG, errbuf);
1350     EXCEPTION
1351       WHEN others THEN
1352         NULL;
1353     END;
1354   END Sync_Soln_Cat_Index;
1355 
1356 PROCEDURE del_sync_prog
1357  IS
1358 BEGIN
1359   fnd_program.delete_program ('CS_KB_SYNC_INDEX', 'CS');
1360   fnd_program.delete_executable ('CS_KB_SYNC_INDEX', 'CS');
1361   COMMIT;
1362 END del_sync_prog;
1363 
1364 
1365 PROCEDURE update_set_count_sum (ERRBUF OUT NOCOPY VARCHAR2,
1366                                 RETCODE OUT NOCOPY NUMBER)
1367   AS
1368 
1369   TYPE list_of_def_id_type IS TABLE OF CS_KB_USED_SUM_DEFS_B.DEF_ID%TYPE
1370     INDEX BY BINARY_INTEGER;
1371   list_of_def_id    list_of_def_id_type;
1372   TYPE list_of_days_type IS TABLE OF CS_KB_USED_SUM_DEFS_B.DAYS%TYPE
1373     INDEX BY BINARY_INTEGER;
1374   list_of_days    list_of_days_type;
1375   i        NUMBER(10);
1376   v_used_count    CS_KB_SET_USED_SUMS.USED_COUNT%TYPE;
1377   current_date    DATE;
1378   whether_exist    NUMBER:=0;
1379   x_user_id NUMBER;
1380   x_login_id NUMBER;
1381 
1382   CURSOR  set_cursor IS
1383     SELECT SET_ID FROM CS_KB_SETS_B;
1384 BEGIN
1385   SELECT SysDate INTO current_date FROM dual;
1386   x_user_id := FND_GLOBAL.user_id;
1387   x_login_id := FND_GLOBAL.login_id;
1388 
1389   SELECT def_id, days BULK COLLECT INTO list_of_def_id, list_of_days
1390           FROM CS_KB_USED_SUM_DEFS_B;
1391 
1392   -- for each set
1393   FOR set_record IN set_cursor LOOP
1394 
1395     -- for each used summary
1396     i:= list_of_def_id.FIRST;
1397     WHILE (i IS NOT NULL) LOOP
1398 
1399       -- count
1400       SELECT count(H.HISTORY_ID) INTO v_used_count
1401       FROM CS_KB_HISTORIES_B H, CS_KB_SET_USED_HISTS USED_HISTS
1402       WHERE H.HISTORY_ID=USED_HISTS.HISTORY_ID AND
1403         USED_HISTS.SET_ID=set_record.set_id AND
1404         USED_HISTS.USED_TYPE=CS_KNOWLEDGE_PVT.G_PF AND
1405         ((current_date-H.entry_date)<=list_of_days(i));
1406 
1407       IF(v_used_count> 0) THEN
1408 
1409         -- insert or update to set_used_sum
1410         SELECT count(SET_ID) INTO whether_exist
1411           FROM CS_KB_SET_USED_SUMS
1412           WHERE SET_ID=set_record.SET_ID AND DEF_ID=list_of_def_id(i);
1413 
1414         IF (whether_exist=0) THEN
1415 
1416           INSERT INTO CS_KB_SET_USED_SUMS (
1417           SET_ID,
1418           DEF_ID,
1419           USED_COUNT,
1420           CREATION_DATE,
1421           CREATED_BY,
1422           LAST_UPDATE_DATE,
1423           LAST_UPDATED_BY,
1424           LAST_UPDATE_LOGIN)
1425           VALUES (
1426           set_record.set_id,
1427           list_of_def_id(i),
1428           v_used_count,
1429           current_date,
1430           x_user_id, --to_number(FND_PROFILE.VALUE ('USER_ID')),
1431           current_date,
1432           x_user_id, --to_number(FND_PROFILE.VALUE ('USER_ID')),
1433           x_login_id --to_number(FND_PROFILE.VALUE('LOGIN_ID'))
1434           );
1435 
1436         ELSE
1437 
1438           UPDATE CS_KB_SET_USED_SUMS SET
1439             USED_COUNT=v_used_count,
1440             LAST_UPDATE_DATE=current_date,
1441             LAST_UPDATED_BY=x_user_id, --to_number(FND_PROFILE.VALUE ('USER_ID')),
1442             LAST_UPDATE_LOGIN=x_login_id --to_number(FND_PROFILE.VALUE('LOGIN_ID'))
1443           WHERE set_id = set_record.set_id
1444           AND def_id = list_of_def_id(i);
1445         END IF;
1446 
1447       ELSIF v_used_count = 0 THEN
1448 
1449          DELETE FROM CS_KB_SET_USED_SUMS
1450          WHERE set_id = set_record.set_id
1451          AND def_id = list_of_def_id(i);
1452 
1453       END IF;
1454 
1455       i:=list_of_def_id.NEXT(i);
1456     END LOOP;
1457   END LOOP;
1458 
1459   --clean up deleted summary definition entries
1460   DELETE FROM cs_kb_set_used_sums
1461   WHERE def_id NOT IN (SELECT def_id
1462   FROM cs_kb_used_sum_defs_b);
1463 
1464   COMMIT;
1465   retcode := 0;
1466 END update_set_count_sum;
1467 
1468 
1469 -- klou (SRCHEFF), since 11.5.10
1470 /**
1471  * UPDATE THE magic word PROFILE.
1472  *
1473  */
1474 PROCEDURE Update_Magic_Word IS
1475   CURSOR Get_Magic_Word_Csr IS
1476     SELECT fnd_profile.value('CS_KB_SEARCH_NONEXIST_KEYWORD') FROM dual;
1477 
1478   CURSOR Test_Magic_Word_Csr(p_keyword VARCHAR2) IS
1479     SELECT NULL
1480     FROM cs_kb_sets_vl SetEO
1481     WHERE
1482     contains(SetEO.composite_assoc_index, p_keyword, 10) >= 1
1483     AND ROWNUM < 2
1484     AND SetEO.status = 'PUB';
1485 
1486   CURSOR Get_Random_Word_Csr IS
1487    /*
1488       dbms_random.string(opt => 'l', len => 8)
1489        different opt VALUES are:
1490        'u' -- upper case
1491        'l' -- lower case
1492        'a' -- alpha characters only (mixed case)
1493        'x' -- any alpha-numeric characters (upper)
1494        'p' -- any printable characters
1495     */
1496    SELECT dbms_random.string( 'l', 5) FROM dual;
1497 
1498   l_magic_word      VARCHAR2(240) := NULL;
1499   l_old_magic_word  VARCHAR2(240) := NULL;
1500   l_result          Test_Magic_Word_Csr%ROWTYPE;
1501 
1502 BEGIN
1503   SAVEPOINT Update_Magic_Word_Sav;
1504    -- get magic word
1505    OPEN Get_Magic_Word_Csr;
1506    FETCH Get_Magic_Word_Csr INTO l_magic_word;
1507    CLOSE Get_Magic_Word_Csr;
1508 
1509    IF l_magic_word IS NULL THEN
1510     OPEN Get_Random_Word_Csr;
1511     FETCH Get_Random_Word_Csr INTO l_magic_word;
1512     CLOSE Get_Random_Word_Csr;
1513 --  l_magic_word := 'xyxyz';
1514    END IF;
1515 
1516    -- Backup l_magic_word
1517    l_old_magic_word := l_magic_word;
1518 --dbms_output.put_line('magic word is '||l_magic_word);
1519    LOOP
1520      OPEN  Test_Magic_Word_Csr(l_magic_word);
1521      FETCH Test_Magic_Word_Csr INTO l_result;
1522      EXIT WHEN Test_Magic_Word_Csr%NOTFOUND;
1523      CLOSE Test_Magic_Word_Csr;
1524 
1525      OPEN Get_Random_Word_Csr;
1526      FETCH Get_Random_Word_Csr INTO l_magic_word;
1527      CLOSE Get_Random_Word_Csr;
1528 
1529    END LOOP;
1530 
1531    IF Test_Magic_Word_Csr%ISOPEN THEN
1532     CLOSE Test_Magic_Word_Csr;
1533    END IF;
1534 
1535    IF l_magic_word <> l_old_magic_word THEN
1536      -- Update profile
1537      IF  Fnd_Profile.Save(
1538            X_NAME  => 'CS_KB_SEARCH_NONEXIST_KEYWORD',  /* Profile name you are setting */
1539            X_VALUE =>  l_magic_word, /* Profile value you are setting */
1540            X_LEVEL_NAME => 'SITE'   /* 'SITE', 'APPL', 'RESP', or 'USER' */
1541            ) THEN
1542        COMMIT WORK;
1543      END IF;
1544    END IF;
1545 
1546 EXCEPTION
1547   WHEN Others THEN
1548    ROLLBACK TO Update_Magic_Word_Sav;
1549 END Update_Magic_Word;
1550 
1551 
1552 PROCEDURE Update_Usage_Score(ERRBUF OUT NOCOPY VARCHAR2,
1553                              RETCODE OUT NOCOPY NUMBER) AS
1554 
1555 BEGIN
1556   SAVEPOINT Update_Usage_Score_Sav;
1557   Cs_Knowledge_Audit_Pvt.Update_Solution_Usage_Score(p_commit =>fnd_api.g_true);
1558   errbuf  := fnd_message.get_string('CS', 'CS_KB_C_SUCCESS');
1559   retcode := 0;
1560 EXCEPTION
1561   WHEN OTHERS THEN
1562     ROLLBACK TO Update_Usage_Score_Sav;
1563     retcode := 2;
1564     errbuf := sqlerrm;
1565     BEGIN
1566         FND_FILE.PUT_LINE(FND_FILE.LOG, errbuf);
1567     EXCEPTION
1568         WHEN others THEN
1569           NULL;
1570     END;
1571 
1572 END Update_Usage_Score;
1573 
1574 
1575   /*
1576    * Rebuild_Soln_Content_Cache
1577    *  Repopulate THE solution content CACHE COLUMN FOR ALL published
1578    *  solutions. Content CACHE entries will be commited IN batches.
1579    */
1580   PROCEDURE Rebuild_Soln_Content_Cache
1581   ( errbuf OUT nocopy VARCHAR2,
1582     retcode OUT nocopy NUMBER )
1583   IS
1584     CURSOR all_published_solutions IS
1585      SELECT tl.set_id
1586      FROM cs_kb_sets_tl tl, cs_kb_sets_b b
1587      WHERE b.set_id = tl.set_id
1588        AND b.status = 'PUB';
1589     TYPE solnIdListType IS TABLE OF cs_kb_sets_tl.set_id%TYPE INDEX BY BINARY_INTEGER;
1590     solnIdList       solnIdListType;
1591     lCommitBatchSize NUMBER          := 100;
1592     lCounter         NUMBER          := 0;
1593   BEGIN
1594     SAVEPOINT start_rebuild_cache;
1595 
1596     -- Fetch out the list of IDs for all published solutions
1597     OPEN all_published_solutions;
1598     FETCH all_published_solutions BULK COLLECT INTO solnIdList;
1599     CLOSE all_published_solutions;
1600 
1601     -- Loop through the solution id list and repopulate the content
1602     -- cache for each solution. Commit will be performed for every
1603     -- lCommitBatchSize repopulations performed.
1604     FOR i IN solnIdList.FIRST..solnIdList.LAST LOOP
1605       cs_kb_sync_index_pkg.populate_soln_content_cache(solnIdList(i));
1606       CS_KB_SYNC_INDEX_PKG.Pop_Soln_Attach_Content_Cache (solnIdList(i));  --12.1.3
1607       lCounter := lCounter + 1;
1608       IF ( lCounter = lCommitBatchSize ) THEN
1609         COMMIT;
1610         lCounter := 0;
1611       END IF;
1612     END LOOP;
1613     COMMIT;
1614     errbuf := fnd_message.get_string('CS', 'CS_KB_C_SUCCESS');
1615     retcode := 0;
1616   EXCEPTION
1617     WHEN others THEN
1618       ROLLBACK TO start_rebuild_cache;
1619       errbuf := 'Rebuild_Soln_Content_Cache: '||fnd_message.GET_STRING('CS','CS_KB_C_UNEXP_ERR')||' '||SQLERRM;
1620       -- Write out error to concurrent program log
1621       BEGIN
1622         FND_FILE.PUT_LINE(FND_FILE.LOG, errbuf);
1623       EXCEPTION
1624         WHEN others THEN
1625           NULL;
1626       END;
1627   END;
1628 
1629   /*
1630    * Mark_Idx_on_Sec_Change
1631    *  Mark text INDEX COLUMNS (solutions AND statements) WHEN KM
1632    *  security setup changes. Marking THE text COLUMNS IS done OFF-line
1633    *  IN a concurrent program TO give better UI response TIME.
1634    *  THE way THE program works IS BY passing IN a security CHANGE
1635    *  action TYPE code. FOR EACH action TYPE, there IS a LIST OF
1636    *  PARAMETERS that get passed THROUGH parameter1-4.
1637    */
1638   PROCEDURE Mark_Idx_on_Sec_Change
1639   ( ERRBUF                       OUT NOCOPY VARCHAR2,
1640     RETCODE                      OUT NOCOPY NUMBER,
1641     SECURITY_CHANGE_ACTION_TYPE  IN         VARCHAR2   DEFAULT NULL,
1642     PARAMETER1                   IN         NUMBER     DEFAULT NULL,
1643     PARAMETER2                   IN         NUMBER     DEFAULT NULL )
1644   IS
1645     l_orig_visibility_id   NUMBER := 0;
1646     l_orig_parent_category_id   NUMBER := 0;
1647     l_visibility_id        NUMBER := 0;
1648     l_category_id          NUMBER := 0;
1649     l_cat_grp_id           NUMBER := 0;
1650   BEGIN
1651     -- Initialize some variables
1652     retcode := ERROR; -- init return val to FAIL
1653 
1654     FND_FILE.PUT_LINE(FND_FILE.LOG, fnd_message.get_string('CS', 'CS_KB_SYNC_IND_BEG')||' '||  'Mark_Idx_on_Sec_Change');
1655 
1656     -- Call out to appropriate helper function for the
1657     -- security setup change action type
1658     IF ( security_change_action_type = 'ADD_VIS' )
1659     THEN
1660       FND_FILE.PUT_LINE(FND_FILE.LOG, fnd_message.get_string('CS', 'CS_KB_SYNC_IND_PROC')||' '||  'ADD_VIS');
1661       l_visibility_id := PARAMETER1;
1662       cs_kb_sync_index_pkg.Mark_Idx_on_Add_Vis( l_visibility_id );
1663     ELSIF ( security_change_action_type = 'REM_VIS' )
1664     THEN
1665       FND_FILE.PUT_LINE(FND_FILE.LOG, fnd_message.get_string('CS', 'CS_KB_SYNC_IND_PROC')||' '||  'REM_VIS');
1666       l_visibility_id := PARAMETER1;
1667       cs_kb_sync_index_pkg.Mark_Idx_on_Rem_Vis( l_visibility_id );
1668     ELSIF ( security_change_action_type = 'CHANGE_CAT_VIS' )
1669     THEN
1670       FND_FILE.PUT_LINE(FND_FILE.LOG, fnd_message.get_string('CS', 'CS_KB_SYNC_IND_PROC')||' '||  'CHANGE_CAT_VIS');
1671       l_category_id := PARAMETER1;
1672       l_orig_visibility_id := PARAMETER2;
1673       cs_kb_sync_index_pkg.Mark_Idx_on_Change_Cat_Vis( l_category_id, l_orig_visibility_id );
1674     ELSIF ( security_change_action_type = 'ADD_CAT_TO_CAT_GRP' )
1675     THEN
1676       FND_FILE.PUT_LINE(FND_FILE.LOG, fnd_message.get_string('CS', 'CS_KB_SYNC_IND_PROC')||' '||  'ADD_CAT_TO_CAT_GRP');
1677       l_cat_grp_id := PARAMETER1;
1678       l_category_id := PARAMETER2;
1679       cs_kb_sync_index_pkg.Mark_Idx_on_Add_Cat_To_Cat_Grp( l_cat_grp_id, l_category_id );
1680     ELSIF ( security_change_action_type = 'REM_CAT_FROM_CAT_GRP' )
1681     THEN
1682       FND_FILE.PUT_LINE(FND_FILE.LOG, fnd_message.get_string('CS', 'CS_KB_SYNC_IND_PROC')||' '||  'REM_CAT_FROM_CAT_GRP');
1683       l_cat_grp_id := PARAMETER1;
1684       l_category_id := PARAMETER2;
1685       cs_kb_sync_index_pkg.Mark_Idx_on_Rem_Cat_fr_Cat_Grp( l_cat_grp_id, l_category_id );
1686     ELSIF ( security_change_action_type = 'CHANGE_PARENT_CAT' )
1687     THEN
1688       FND_FILE.PUT_LINE(FND_FILE.LOG, fnd_message.get_string('CS', 'CS_KB_SYNC_IND_PROC')||' '||  'CHANGE_PARENT_CAT');
1689       l_category_id := PARAMETER1;
1690       l_orig_parent_category_id := PARAMETER2;
1691       cs_kb_sync_index_pkg.Mark_Idx_on_Change_Parent_Cat( l_category_id, l_orig_parent_category_id );
1692     ELSE -- invalid action
1693 
1694       FND_FILE.PUT_LINE(FND_FILE.LOG, fnd_message.get_string('CS', 'CS_KB_SYNC_IND_INV_TYPE'));
1695 --  'Error: Invalid change security setup action type specified'
1696       RAISE invalid_action_error;
1697     END IF;
1698     COMMIT;
1699     -- Set return value and log message to Success
1700     FND_FILE.PUT_LINE(FND_FILE.LOG, fnd_message.get_string('CS', 'CS_KB_SYNC_SUCESS_END'));
1701 -- 'Successfully Completed.'
1702     errbuf := fnd_message.get_string('CS', 'CS_KB_C_SUCCESS');
1703     retcode := SUCCESS;
1704 
1705   EXCEPTION
1706     WHEN invalid_action_error THEN
1707       BEGIN
1708         errbuf := fnd_message.get_string('CS', 'CS_KB_SYN_INDEX_INV_ACT');
1709 --  'Invalid action specified'
1710       END;
1711     WHEN others THEN
1712       ROLLBACK;
1713       errbuf := 'Mark_Idx_on_Sec_Change: '||fnd_message.GET_STRING('CS','CS_KB_C_UNEXP_ERR')||' '||SQLERRM;
1714       -- Write out error to concurrent program log
1715       BEGIN
1716         FND_FILE.PUT_LINE(FND_FILE.LOG, errbuf);
1717       EXCEPTION
1718         WHEN others THEN
1719           NULL;
1720       END;
1721   END Mark_Idx_on_Sec_Change;
1722 
1723 END CS_KB_CONC_PROG_PKG;