DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGS_PE_SET_REM_HOLDS

Source


1 PACKAGE BODY igs_pe_set_rem_holds AS
2 /* $Header: IGSPE08B.pls 120.2 2006/02/02 06:57:24 skpandey noship $ */
3 
4   ------------------------------------------------------------------
5   --Created by  : Sanil Madathil, Oracle IDC
6   --Date created: 25-SEP-2001
7   --
8   --Purpose: Package Body contains code for procedures/Functions defined in
9   --         package specification . Also body includes Functions/Procedures
10   --         private to it .
11   --
12   --
13   --Known limitations/enhancements and/or remarks:
14   --
15   --Change History:
16   --Who         When            What
17   --npalanis    30-apr-2002     The display of person id during setting or releasing
18   --                            holds is changed to person number.
19   --                            The full name is nullable so nvl of space is given for
20   --                            full name.
21   --ssawhney    17-feb-2003     Bug 2758856  external holds design change, ENCUMB TBH parameter added.
22   --pkpatel     8-APR-2003      Bug 2804863. Modified set_prsid_grp_holds and rel_prsid_grp_holds procedures.
23   --gmaheswa    29-OCT-2003     Bug 3198795  Modified set_prsid_grp_holds and rel_prsid_grp_holds procedures for
24   --                                         Introducing dynamic person id groups.
25   --asbala      26-DEC-2003     3338759, Modified the substr() call to retrieve l_seq_num in set_prsid_grp_holds.
26   --                In rel_prsid_grp_holds, when the hold doesnot exist, the process will not
27   --                error out. Added ROLLBACK stmts in set_prsid_grp_holds and rel_prsid_grp_holds.
28   --pkpatel     6-JAn-2004     3338759, Used TRIM for Cal type in Rel, Moved the Savepoint before Begin in Set Hold
29   -------------------------------------------------------------------
30 
31   FUNCTION lookup_desc( l_type IN VARCHAR2 ,
32                         l_code IN VARCHAR2 )
33                         RETURN VARCHAR2 IS
34   ------------------------------------------------------------------
35   --Created by  : Sanil Madathil, Oracle IDC
36   --Date created: 25-SEP-2001
37   --
38   --Purpose: This function is private to this package body . This Procedure returns the
39   --         meaning from look up table
40   --
41   --
42   --
43   --Known limitations/enhancements and/or remarks:
44   --
45   --Change History:
46   --Who         When            What
47   -------------------------------------------------------------------
48 
49     CURSOR c_desc( x_type igs_lookups_view.lookup_type%TYPE , x_code  igs_lookups_view.lookup_code%TYPE ) IS
50     SELECT meaning
51     FROM   igs_lookups_view
52     WHERE  lookup_code = x_code
53     AND    lookup_type = x_type ;
54 
55     l_desc igs_lookups_view.meaning%TYPE ;
56 
57  BEGIN
58 
59    IF l_code IS NULL THEN
60      RETURN NULL ;
61    ELSE
62       OPEN c_desc(l_type,l_code);
63       FETCH c_desc INTO l_desc ;
64       CLOSE c_desc ;
65    END IF ;
66 
67    RETURN l_desc ;
68 
69  END lookup_desc;  /** Function Ends Here   **/
70 
71 
72   PROCEDURE log_messages ( p_msg_name  VARCHAR2 ,
73                            p_msg_val   VARCHAR2
74                          ) IS
75   ------------------------------------------------------------------
76   --Created by  : Sanil Madathil, Oracle IDC
77   --Date created: 25-SEP-2001
78   --
79   --Purpose: This procedure is private to this package body .
80   --         The procedure logs all the parameter values ,
81   --         table values
82   --
83   --
84   --Known limitations/enhancements and/or remarks:
85   --
86   --Change History:
87   --Who         When            What
88   -------------------------------------------------------------------
89   BEGIN
90     FND_MESSAGE.SET_NAME('IGS','IGS_FI_CAL_BALANCES_LOG');
91     FND_MESSAGE.SET_TOKEN('PARAMETER_NAME',p_msg_name);
92     FND_MESSAGE.SET_TOKEN('PARAMETER_VAL' ,p_msg_val) ;
93     FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.GET);
94   END log_messages ;
95 
96   PROCEDURE set_prsid_grp_holds ( errbuf           OUT NOCOPY VARCHAR2                                         ,
97                                   retcode          OUT NOCOPY NUMBER                                           ,
98                                   p_hold_type      IN  igs_pe_pers_encumb_v.encumbrance_type%TYPE       ,
99                                   p_pid_group      IN  igs_pe_persid_group_v.group_id%TYPE              ,
100                                   p_start_dt       IN  VARCHAR2                                         ,
101                                   p_term           IN  VARCHAR2                                         ,
102                                   p_org_id         IN  NUMBER
103                                  ) IS
104   ------------------------------------------------------------------
105   --Created by  : Sanil Madathil, Oracle IDC
106   --Date created: 25-SEP-2001
107   --
108   --Purpose: The concurrent manager initiates this procedure. This concurrent process set
109   --         new holds for all members in a person ID group , using the specified parameters.
110   --
111   --
112   --Known limitations/enhancements and/or remarks:
113   --
114   --Change History:
115   --Who         When            What
116   --pkpatel     30-SEP-2002     Bug NO: 2600842
117   --                            Added the validation for implementing security feature with respect to Authorising Person.
118   --                            Removed the parameter p_authorizing_id
119   --                            Added the check to consider only the active members of the person ID group
120   --                            Call the user defined exception instead of app_exception.raise_exception, so that
121   --                            the message Unhandled Exception does not come for business validations failed
122   --ssawhney    17-feb-2003     Bug 2758856  external holds design change, ENCUMB TBH parameter added.
123   --pkpatel     8-APR-2003      Bug 2804863 igs_pe_gen_001.g_hold_validation variable was set to 'N' at the beginning and 'Y' at the end.
124   --gmaheswa    29-OCT-2003     Bug 3198795 Introducing DYNAMIC PERSON ID group functionality
125   --asbala      5-JAN-2003      3338759, Changes mentioned along with bug no. in corresponding places
126   --skpandey    02-FEB-2006     Bug#4937960: Changed call to igs_get_dynamic_sql to get_dynamic_sql as a part of literal fix
127   -------------------------------------------------------------------
128     l_cal_type       igs_ca_inst.cal_type%TYPE        ;
129     l_seq_num        igs_ca_inst.sequence_number%TYPE ;
130     l_start_date     igs_ca_inst.start_dt%TYPE        ;
131     l_rowid          igs_pe_prsid_grp_mem.row_id%TYPE;
132     l_message_name   VARCHAR2(30)   ;
133     l_message_string VARCHAR2(900)  ;
134     l_msg_str_0      VARCHAR2(1000) ;
135     l_msg_str_1      VARCHAR2(1000) ;
136     l_err_raised     BOOLEAN := FALSE;
137     l_resp_id      fnd_responsibility.responsibility_id%TYPE := FND_GLOBAL.RESP_ID;
138 
139     l_error_exception  EXCEPTION ;  /* user defined exception */
140     l_person_id    hz_parties.party_id%TYPE;
141     l_person_number hz_parties.party_number%TYPE;
142     l_person_name   hz_person_profiles.person_name%TYPE;
143 
144     L_select VARCHAR2(32767) := 'SELECT p.person_id,p.person_number,p.full_name FROM igs_pe_person_base_v p WHERE p.person_id IN ';
145     TYPE cur_query IS REF CURSOR;
146     c_cur_query cur_query;
147 
148     TYPE rec_query IS RECORD (
149           person_id     NUMBER(30),
150           person_number VARCHAR2(100),
151           full_name  VARCHAR2(240)
152       );
153     r_rec_query rec_query;
154 
155     L_str VARCHAR2(32000);
156     l_status VARCHAR2(1);
157 
158     l_group_type IGS_PE_PERSID_GROUP_V.group_type%TYPE;
159 
160   BEGIN
161 
162     IGS_GE_GEN_003.set_org_id(p_org_id) ;                /**  sets the orgid                      **/
163     retcode := 0 ;                                       /**  initialises the out NOCOPY parameter to 0  **/
164 
165      -- Set the variable to 'N' to prevent the security level validation to happen for each record.
166     igs_pe_gen_001.g_hold_validation := 'N';
167 
168     IF p_term IS NOT NULL THEN
169       l_cal_type   := TRIM(SUBSTR(p_term,1,10)) ;
170       l_seq_num    := FND_NUMBER.CANONICAL_TO_NUMBER(SUBSTR(p_term,-6)) ; --3338759: To get the 6-digit sequence number
171       l_start_date := IGS_GE_DATE.IGSDATE(SUBSTR(p_term,12,10));
172     ELSE
173       l_start_date  :=  IGS_GE_DATE.IGSDATE(p_start_dt) ;  /**  Character to date conversion        **/
174     END IF;
175 
176     -- logs all the parameters
177     log_messages(RPAD(lookup_desc('IGS_PE_HOLDS','PERS_ID_GROUP'),20)||':',p_pid_group);
178     log_messages(RPAD(lookup_desc('IGS_PE_HOLDS','HOLD_TYPE'),20)||':',p_hold_type);
179 
180     -- if p_term parameter is entered by the user only then this parameter is logged in log file
181     IF p_term IS NOT NULL THEN
182       log_messages(RPAD(lookup_desc('IGS_PE_HOLDS','TERM'),20)||':',p_term);
183       log_messages(RPAD(lookup_desc('IGS_PE_HOLDS','CAL_TYPE'),20)||':',l_cal_type);
184       log_messages(RPAD(lookup_desc('IGS_PE_HOLDS','SEQ_NUM'),20)||':',l_seq_num);
185     END IF;
186 
187     log_messages(RPAD(lookup_desc('IGS_PE_HOLDS','START_DT'),20)||':',IGS_GE_DATE.IGSCHARDT(l_start_date));
188 
189     FND_FILE.NEW_LINE(FND_FILE.LOG,2);                    /** writes 2 new line characters **/
190 
191     -- if both start date and term parameters are passed as null , error out NOCOPY of the process
192     IF p_start_dt IS NULL AND p_term IS NULL THEN
193         FND_MESSAGE.SET_NAME('IGS','IGS_PE_TERM_OR_START_DT') ;
194         IGS_GE_MSG_STACK.ADD;
195         RAISE l_error_exception;
196     END IF;
197 
198     -- if both start date and term parameters are passed as not null's , error out NOCOPY of the process
199     IF p_start_dt IS NOT NULL AND p_term IS NOT NULL THEN
200         FND_MESSAGE.SET_NAME('IGS','IGS_PE_TERM_OR_START_DT') ;
201         IGS_GE_MSG_STACK.ADD;
202         RAISE l_error_exception;
203     END IF;
204 
205      -- Validate that the person who has logged in has a party account and
206      -- is a STAFF. If he fails any of the above then is not authorized to release the hold.
207        igs_pe_gen_001.get_hold_auth(FND_GLOBAL.USER_ID,
208                                   l_person_id,
209                                   l_person_number,
210                                   l_person_name,
211                                   l_message_name);
212 
213       IF l_message_name IS NOT NULL THEN
214         FND_MESSAGE.SET_NAME('IGS',l_message_name) ;
215         IGS_GE_MSG_STACK.ADD;
216         RAISE l_error_exception;
217      END IF;
218 
219      -- ssawhney commented the above call as its already happening in the TBH
220 
221     l_msg_str_0  :=   RPAD(lookup_desc('IGS_PE_HOLDS','PERSON'),30) ||
222                       RPAD(lookup_desc('IGS_PE_HOLDS','NAME'),452)||
223                       RPAD(lookup_desc('IGS_PE_HOLDS','HOLD_TYPE'),12)||
224                       RPAD(lookup_desc('IGS_PE_HOLDS','CAL_TYPE'),15)||
225                       RPAD(lookup_desc('IGS_PE_HOLDS','SEQ_NUM'),17)||
226                       RPAD(lookup_desc('IGS_PE_HOLDS','START_DT'),11);
227 
228     FND_FILE.PUT_LINE(FND_FILE.LOG,l_msg_str_0);
229     FND_FILE.PUT_LINE(FND_FILE.LOG,' ');
230 
231    --get the query for the members in the group passed
232    L_str := igs_pe_dynamic_persid_group.get_dynamic_sql(p_pid_group,l_status, l_group_type);
233    IF l_status <> 'S' THEN
234       RAISE NO_DATA_FOUND;
235    END IF;
236    L_select := L_select||'('||L_str||')';
237    --skpandey, Bug#4937960: Added logic as a part of literal fix
238    IF l_group_type = 'STATIC' THEN
239     OPEN c_cur_query FOR L_select USING p_pid_group ;
240    ELSIF l_group_type = 'DYNAMIC' THEN
241     OPEN c_cur_query FOR L_select;
242    END IF;
243     LOOP
244       FETCH c_cur_query INTO r_rec_query; ----l_per_id,l_per_number,l_full_name;
245       EXIT WHEN c_cur_query%NOTFOUND;
246       SAVEPOINT sp_person;
247       l_err_raised := FALSE ;
248       BEGIN
249         l_msg_str_1    :=  RPAD(r_rec_query.person_number,30) ||
250                            RPAD(NVL(r_rec_query.full_name,' '),452)         ||
251                            RPAD(p_hold_type,12)                   ||
252                            NVL(RPAD(l_cal_type,15),'               ')||
253                            NVL(RPAD(TO_CHAR(l_seq_num),17),'                 ')||
254                            RPAD(IGS_GE_DATE.IGSCHARDT(l_start_date),11) ;
255         FND_FILE.PUT_LINE(FND_FILE.LOG,l_msg_str_1);
256 
257 		igs_pe_pers_encumb_pkg.insert_row
258         (
259               x_mode                     =>   'R'                     ,
260               x_rowid                    =>   l_rowid                 ,
261               x_person_id                =>   r_rec_query.person_id    ,
262               x_encumbrance_type         =>   p_hold_type             ,
263               x_start_dt                 =>   l_start_date            ,
264               x_expiry_dt                =>   NULL                    ,
265               x_authorising_person_id    =>   l_person_id,
266               x_comments                 =>   NULL                    ,
267               x_spo_course_cd            =>   NULL                    ,
268               x_spo_sequence_number      =>   NULL                    ,
269               x_cal_type                 =>   l_cal_type              ,
270               x_sequence_number          =>   l_seq_num ,
271               x_auth_resp_id             =>   l_resp_id ,
272               x_external_reference       =>   NULL   -- this should be explicitly NULL while coming from Internal system
273         ) ;
274 
275       EXCEPTION
276         WHEN OTHERS THEN
277           l_err_raised := TRUE ;
278           FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.GET);
279           ROLLBACK TO sp_person; -- 3338759: Rollback to SAVEPOINT sp_person in case of exception
280       END ;
281 
282       IF NOT (l_err_raised) THEN
283     BEGIN
284           --check if the encumbrance has effects which require that the active
285           -- enrolments be dicontinued , validate that SCA'S are inactive
286           IF igs_en_val_pen.finp_val_encmb_eff ( r_rec_query.person_id ,
287                                                  p_hold_type          ,
288                                                  l_start_date         ,
289                                                  NULL                 ,
290                                                  l_message_name
291                                                 ) = FALSE
292           THEN
293             ROLLBACK TO sp_person;
294             FND_MESSAGE.SET_NAME('IGS',l_message_name) ;
295             IGS_GE_MSG_STACK.ADD;
296             RAISE l_error_exception ;
297           END IF;
298 
299           -- call the procedure which creates the default effects for the encumbrance type .
300           igs_en_gen_009.enrp_ins_dflt_effect ( r_rec_query.person_id ,
301                                                 p_hold_type          ,
302                                                 l_start_date         ,
303                                                 NULL                 ,
304                                                 NULL                 ,
305                                                 l_message_name       ,
306                                                 l_message_string
307                                                ) ;
308           IF l_message_name IS NOT NULL THEN
309             ROLLBACK TO sp_person;
310             FND_MESSAGE.SET_NAME('IGS',l_message_name) ;
311             IGS_GE_MSG_STACK.ADD;
312             RAISE l_error_exception ;
313           END IF;
314 
315     EXCEPTION
316       WHEN OTHERS THEN
317 	FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.GET);
318     END ;
319     END IF;
320     END LOOP ;
321     CLOSE c_cur_query;
322     igs_pe_gen_001.g_hold_validation := 'Y';
323 
324   EXCEPTION
325     WHEN NO_DATA_FOUND THEN
326       retcode := 2;
327       igs_pe_gen_001.g_hold_validation := 'Y';
328       FND_MESSAGE.SET_NAME('IGS','IGS_PE_PERSID_GROUP_EXP') ;
329       FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.GET);
330     WHEN l_error_exception THEN
331      retcode := 2;
332      igs_pe_gen_001.g_hold_validation := 'Y';
333      FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.GET);
334 
335     WHEN OTHERS THEN
336       retcode := 2;
337       igs_pe_gen_001.g_hold_validation := 'Y';
338       errbuf  := FND_MESSAGE.GET_STRING('IGS','IGS_GE_UNHANDLED_EXCEPTION');
339       IGS_GE_MSG_STACK.CONC_EXCEPTION_HNDL ;
340 
341   END set_prsid_grp_holds ;                      /** procedure ends here **/
342 
343 
344   PROCEDURE rel_prsid_grp_holds ( errbuf           OUT NOCOPY VARCHAR2                                         ,
345                                   retcode          OUT NOCOPY NUMBER                                           ,
346                                   p_hold_type      IN  igs_pe_pers_encumb_v.encumbrance_type%TYPE       ,
347                                   p_pid_group      IN  igs_pe_persid_group_v.group_id%TYPE              ,
348                                   p_start_dt       IN  VARCHAR2                                         ,
349                                   p_expiry_dt      IN  VARCHAR2                                         ,
350                                   p_term           IN  VARCHAR2                                         ,
351                                   p_org_id         IN  NUMBER
352                                  ) IS
353   ------------------------------------------------------------------
354   --Created by  : Sanil Madathil, Oracle IDC
355   --Date created: 25-SEP-2001
356   --
357   --Purpose: The concurrent manager initiates this procedure. This concurrent process release
358   --         holds for all memebers in a person ID group, using the specified parameters and
359   --         logic.
360   --
361   --Known limitations/enhancements and/or remarks:
362   --
363   --Change History:
364   --Who         When            What
365   --pkpatel     30-SEP-2002     Bug NO: 2600842
366   --                            Added the validation for implementing security feature with respect to Authorising Person.
367   --                            Removed the parameter p_authorizing_id
368   --                            Added the check to consider only the active members of the person ID group
369   --                            Call the user defined exception instead of app_exception.raise_exception, so that
370   --                            the message Unhandled Exception does not come for business validations failed
371   --pkpatel     8-APR-2003      Bug 2804863 igs_pe_gen_001.g_hold_validation variable was set to 'N' at the beginning and 'Y' at the end.
372   --                            Added the call of igs_pe_gen_001.get_hold_auth
373   --gmaheswa    29-OCT-2003     Bug 3198795 Introducing DYNAMIC PERSON ID group functionality
374   --skpandey    12-JAN-2006     Bug#4937960
375   --                            Changed c_igs_pe_pers_encumb Cursor definition to optimize query
376   --skpandey    02-FEB-2006     Bug#4937960: Changed call to igs_get_dynamic_sql to get_dynamic_sql as a part of literal fix
377   -------------------------------------------------------------------
378     l_cal_type       igs_ca_inst.cal_type%TYPE         ;
379     l_seq_num        igs_ca_inst.sequence_number%TYPE  ;
380     l_start_date     igs_ca_inst.start_dt%TYPE ;
381     l_expiry_date    igs_ca_inst.start_dt%TYPE ;
382     l_rowid          igs_pe_prsid_grp_mem.row_id%TYPE;
383     l_message_name   VARCHAR2(30);
384     l_message_string VARCHAR2(900);
385     l_msg_str_0      VARCHAR2(1000);
386     l_msg_str_1      VARCHAR2(1000);
387     l_err_raised     BOOLEAN := FALSE;
388 
389     l_resp_id      fnd_responsibility.responsibility_id%TYPE := FND_GLOBAL.RESP_ID;
390     l_fnd_user_id  fnd_user.user_id%TYPE := FND_GLOBAL.USER_ID;
391     l_person_id    hz_parties.party_id%TYPE;
392     l_person_number hz_parties.party_number%TYPE;
393     l_person_name   hz_person_profiles.person_name%TYPE;
394 
395 
396     -- cursor selects row_id from igs_pe_pers_encumb table based on person id and hold type
397     CURSOR c_igs_pe_pers_encumb(cp_person_id  igs_pe_pers_encumb_v.person_id%TYPE               ,
398                                           cp_hold_type  igs_pe_pers_encumb_v.encumbrance_type%TYPE ,
399                                           cp_start_dt   igs_pe_pers_encumb_v.start_dt%TYPE) IS
400     SELECT           *
401     FROM             IGS_PE_PERS_ENCUMB
402     WHERE            person_id         = cp_person_id
403     AND              encumbrance_type  = cp_hold_type
404     AND              start_dt          = cp_start_dt
405     AND              (expiry_dt IS NULL OR SYSDATE < expiry_dt);
406 
407     l_c_igs_pe_pers_encumb   c_igs_pe_pers_encumb%ROWTYPE ;  -- cursor variable for the above cursor
408     l_error_exception  EXCEPTION ;  /* user defined exception */
409     l_ignore_exception  EXCEPTION ;  /* user defined exception */ -- for logging the error and stopping of further processing.
410                                   -- concurrent pgm will not error out.
411     L_select VARCHAR2(32767) := 'SELECT p.person_id,p.person_number,p.full_name FROM igs_pe_person_base_v p WHERE p.person_id IN ';
412     TYPE cur_query IS REF CURSOR;
413     c_cur_query cur_query;
414 
415     TYPE rec_query IS RECORD (
416           person_id     NUMBER(30),
417           person_number VARCHAR2(100),
418           full_name  VARCHAR2(240)
419       );
420     r_rec_query rec_query;
421 
422     L_str VARCHAR2(32000);
423     l_status VARCHAR2(1);
424 
425     l_group_type IGS_PE_PERSID_GROUP_V.group_type%type;
426 
427   BEGIN
428     IGS_GE_GEN_003.set_org_id(p_org_id) ;                /**  sets the orgid                      **/
429     retcode := 0 ;                                       /**  initialises the out NOCOPY parameter to 0  **/
430 
431     -- Set the variable to 'N' to prevent the security level validation to happen for each record.
432     igs_pe_gen_001.g_hold_validation := 'N';
433 
434     IF p_term IS NOT NULL THEN
435       l_cal_type    := TRIM(SUBSTR(p_term,1,10)) ;
436       l_seq_num     := FND_NUMBER.CANONICAL_TO_NUMBER(SUBSTR(p_term,-6)); --3338759: To get the 6-digit sequence number
437       l_start_date  := IGS_GE_DATE.IGSDATE(SUBSTR(p_term,12,10));
438       l_expiry_date := IGS_GE_DATE.IGSDATE(SUBSTR(p_term,23,10));
439     ELSE
440       l_start_date   :=  IGS_GE_DATE.IGSDATE(p_start_dt) ;   /**  Character to date conversion        **/
441       l_expiry_date  :=  IGS_GE_DATE.IGSDATE(p_expiry_dt) ;  /**  Character to date conversion        **/
442     END IF;
443 
444     -- logs all the parameters
445     log_messages(RPAD(lookup_desc('IGS_PE_HOLDS','PERS_ID_GROUP'),20)||':',p_pid_group);
446     log_messages(RPAD(lookup_desc('IGS_PE_HOLDS','HOLD_TYPE'),20)||':',p_hold_type);
447 
448     -- if p_term parameter is entered by the user only then this parameter is logged in log file
449     IF p_term IS NOT NULL THEN
450       log_messages(RPAD(lookup_desc('IGS_PE_HOLDS','TERM'),20)||':',p_term);
451       log_messages(RPAD(lookup_desc('IGS_PE_HOLDS','CAL_TYPE'),20)||':',l_cal_type);
452       log_messages(RPAD(lookup_desc('IGS_PE_HOLDS','SEQ_NUM'),20)||':',l_seq_num);
453     END IF;
454 
455     log_messages(RPAD(lookup_desc('IGS_PE_HOLDS','START_DT'),20)||':',IGS_GE_DATE.IGSCHARDT(l_start_date));
456     log_messages(RPAD(lookup_desc('IGS_PE_HOLDS','EXPIRY_DT'),20)||':',IGS_GE_DATE.IGSCHARDT(l_expiry_date));
457     FND_FILE.NEW_LINE(FND_FILE.LOG,2);                    /** writes 2 new line characters **/
458 
459     -- if both start date and term parameters are passed as null , error out of the process
460     IF ((p_start_dt IS NULL OR p_expiry_dt IS NULL) AND p_term IS NULL) THEN
461         FND_MESSAGE.SET_NAME('IGS','IGS_PE_TERM_OR_START_EXP_DT') ;
462         IGS_GE_MSG_STACK.ADD;
463         RAISE l_error_exception;
464     END IF;
465 
466     -- if both start date and term parameters are passed as not null's , error out of the process
467     IF ((p_start_dt IS NOT NULL OR p_expiry_dt IS NOT NULL) AND p_term IS NOT NULL) THEN
468         FND_MESSAGE.SET_NAME('IGS','IGS_PE_TERM_OR_START_EXP_DT') ;
469         IGS_GE_MSG_STACK.ADD;
470         RAISE l_error_exception;
471     END IF;
472 
473     -- check if expirt date is less than start date
474       IF l_expiry_date < l_start_date THEN
475         FND_MESSAGE.SET_NAME('IGS','IGS_EN_EXPDT_GE_STDT') ;
476         IGS_GE_MSG_STACK.ADD;
477         RAISE l_error_exception;
478       END IF;
479 
480      -- Validate that the person who has logged in has a party account and
481      -- is a STAFF. If he fails any of the above then is not authorized to release the hold.
482        igs_pe_gen_001.get_hold_auth(FND_GLOBAL.USER_ID,
483                                     l_person_id,
484                                     l_person_number,
485                                     l_person_name,
486                                     l_message_name);
487 
488       IF l_message_name IS NOT NULL THEN
489         FND_MESSAGE.SET_NAME('IGS',l_message_name) ;
490         IGS_GE_MSG_STACK.ADD;
491         RAISE l_error_exception;
492       END IF;
493 
494     l_msg_str_0  :=   RPAD(lookup_desc('IGS_PE_HOLDS','PERSON'),30) ||
495                       RPAD(lookup_desc('IGS_PE_HOLDS','NAME'),452);
496 
497     FND_FILE.PUT_LINE(FND_FILE.LOG,l_msg_str_0);
498     FND_FILE.PUT_LINE(FND_FILE.LOG,' ');
499 
500     --get the query for the members in the group passed
501     L_str := igs_pe_dynamic_persid_group.get_dynamic_sql(p_pid_group,l_status, l_group_type); -- skpandey
502     IF l_status <> 'S' THEN
503       RAISE NO_DATA_FOUND;
504     END IF;
505     L_select := L_select||'('||L_str||')';
506 
507    --skpandey, Bug#4937960: Added logic as a part of literal fix
508    IF l_group_type = 'STATIC' THEN
509     OPEN c_cur_query FOR L_select USING p_pid_group ;
510    ELSIF l_group_type = 'DYNAMIC' THEN
511     OPEN c_cur_query FOR L_select;
512    END IF;
513     LOOP
514       FETCH c_cur_query INTO r_rec_query ; --l_per_id,l_per_number,l_full_name;
515       EXIT WHEN c_cur_query%NOTFOUND;
516       BEGIN
517         l_msg_str_1    :=  RPAD(r_rec_query.person_number,30) ||
518                            RPAD(nvl(r_rec_query.full_name,' '),452);
519 
520         FND_FILE.PUT_LINE(FND_FILE.LOG,l_msg_str_1);
521 
522         OPEN   c_igs_pe_pers_encumb( cp_person_id    =>  r_rec_query.person_id ,
523                                      cp_hold_type    =>  p_hold_type          ,
524                                      cp_start_dt     =>  l_start_date
525                                     );
526         FETCH  c_igs_pe_pers_encumb INTO l_c_igs_pe_pers_encumb ;
527         IF c_igs_pe_pers_encumb%NOTFOUND THEN
528           CLOSE  c_igs_pe_pers_encumb ;
529           FND_MESSAGE.SET_NAME('IGS','IGS_PE_PERS_ENCUMB_NOTEXIST') ;
530           IGS_GE_MSG_STACK.ADD;
531       RAISE l_ignore_exception; -- 3338759: To stop further processing and log the message
532         END IF;
533         CLOSE  c_igs_pe_pers_encumb ;
534 
535         BEGIN
536 
537         -- Person Encumbrance Security.
538         -- To release Hold the user must have a party account
539         -- must be a Staff
540         -- must have logged in with the same responsibility as the Authorizer has logged in to create the Hold.
541         SAVEPOINT sp_release;
542 
543             igs_pe_gen_001.release_hold
544             (p_resp_id     => l_resp_id,
545              p_fnd_user_id => l_fnd_user_id,
546              p_person_id   => r_rec_query.person_id,
547              p_encumbrance_type => p_hold_type,
548              p_start_dt    => l_start_date,
549              p_expiry_dt   => l_expiry_date,
550              p_override_resp => 'N',
551              p_message_name  => l_message_name);
552 
553         EXCEPTION
554           WHEN OTHERS THEN
555             -- 3338759: Rollback to SAVEPOINT sp_release in case of exception
556         ROLLBACK TO sp_release;
557         retcode := 2;
558             FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.GET);
559         END ;
560      EXCEPTION
561        WHEN l_error_exception THEN
562        retcode := 2;
563            FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.GET);
564 
565        WHEN l_ignore_exception THEN -- 3338759: when this exception is thrown, only the error is to be logged
566                                     -- the concurrent program should not error out
567            FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.GET);
568      END ;
569     END LOOP ;
570     CLOSE c_cur_query;
571     igs_pe_gen_001.g_hold_validation := 'Y';
572 
573   EXCEPTION
574     WHEN NO_DATA_FOUND THEN
575       retcode := 2;
576       igs_pe_gen_001.g_hold_validation := 'Y';
577       FND_MESSAGE.SET_NAME('IGS','IGS_PE_PERSID_GROUP_EXP') ;
578       FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.GET);
579 
580     WHEN l_error_exception THEN
581      retcode := 2;
582      igs_pe_gen_001.g_hold_validation := 'Y';
583      FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.GET);
584 
585     WHEN OTHERS THEN
586       retcode := 2;
587       igs_pe_gen_001.g_hold_validation := 'Y';
588       errbuf  := FND_MESSAGE.GET_STRING('IGS','IGS_GE_UNHANDLED_EXCEPTION');
589       IGS_GE_MSG_STACK.CONC_EXCEPTION_HNDL ;
590   END rel_prsid_grp_holds ;                      /** procedure ends here **/
591 END igs_pe_set_rem_holds;