DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGS_EN_DROP_UNITS_API

Source


1 PACKAGE BODY igs_en_drop_units_api AS
2 /* $Header: IGSEN92B.pls 120.13 2006/08/24 07:27:08 bdeviset noship $ */
3 
4 --package variables
5 g_debug_level               CONSTANT NUMBER  := FND_LOG.G_CURRENT_RUNTIME_LEVEL;
6 
7 
8       CURSOR C_SUA_lock (cp_person_id igs_en_su_attempt_all.person_id%TYPE,
9                           cp_course_cd igs_en_su_attempt_all.course_cd%TYPE,
10                          cp_uoo_id igs_en_su_attempt_all.uoo_id%TYPE) IS
11       SELECT unit_attempt_status
12       FROM IGS_EN_SU_ATTEMPT_ALL sua
13       WHERE person_id = cp_person_id AND
14             course_cd = cp_course_cd AND
15             uoo_id = cp_uoo_id
16       FOR UPDATE NOWAIT;
17       l_lock_rec  C_SUA_lock%ROWTYPE;
18 
19 
20   FUNCTION is_unit_subordinate(
21                                p_person_id        IN igs_en_su_attempt.person_id%TYPE,
22                                p_course_cd        IN igs_en_su_attempt.course_cd%TYPE,
23                                p_uoo_id           IN igs_en_su_attempt.uoo_id%TYPE,
24                                p_drop_alluoo_ids  IN VARCHAR2
25                               ) RETURN VARCHAR2 AS
26 
27  -------------------------------------------------------------------------------------------
28   -- Created by  : Basanth Kumar D, Oracle Student Systems Oracle IDC
29   -- Purpose : This procedure checks wheter the passed unit is a subordinate unit or not and
30   --           returns the same
31   --Change History:
32   --Who         When            What
33   -------------------------------------------------------------------------------------------
34 
35     l_sub_unit VARCHAR2(1);
36     l_sup_unitcd           igs_en_su_attempt.sup_unit_cd%TYPE;
37     l_sup_version          igs_en_su_attempt.sup_version_number%TYPE;
38 
39     TYPE c_ref_cursor IS REF CURSOR;
40     c_chk_is_sub c_ref_cursor;
41 
42 
43   BEGIN
44     --modified sqlquery for bug 5037726,sqlid :14792699
45     OPEN c_chk_is_sub FOR
46                         'SELECT sua.sup_unit_cd ,sua.sup_version_number
47                          FROM igs_en_su_attempt sua
48                          WHERE sua.uoo_id =:1
49                          AND sua.person_id =:2
50                          AND sua.course_cd =:3
51                          AND EXISTS
52                                     (SELECT ''X'' FROM igs_ps_unit_ofr_opt uoo
53                                      WHERE uoo.sup_uoo_id IN (' ||p_drop_alluoo_ids||')
54                                      AND uoo.relation_type = ''SUBORDINATE''
55                                      AND uoo.uoo_id = sua.uoo_id)' USING p_uoo_id,p_person_id,p_course_cd;
56 
57     FETCH c_chk_is_sub INTO l_sup_unitcd, l_sup_version;
58 
59     l_sub_unit := 'N';
60     IF c_chk_is_sub%FOUND THEN
61 
62         l_sub_unit := 'Y';
63 
64     END IF;
65 
66     CLOSE c_chk_is_sub;
67 
68     RETURN l_sub_unit;
69 
70   EXCEPTION
71     WHEN OTHERS THEN
72       Fnd_Message.Set_Name('IGS','IGS_GE_UNHANDLED_EXP');
73       FND_MESSAGE.SET_TOKEN('NAME', 'IGS_EN_DROP_UNITS_API.is_unit_subordinate');
74       IGS_GE_MSG_STACK.ADD;
75       IF (FND_LOG.LEVEL_UNEXPECTED >= g_debug_level ) THEN
76             FND_LOG.STRING(fnd_log.level_unexpected, 'igs.patch.115.sql.igs_en_drop_units_api.is_unit_subordinate :',SQLERRM);
77       END IF;
78       RAISE;
79   END is_unit_subordinate;
80 
81 
82   PROCEDURE drop_units(
83                             p_person_id               IN igs_en_su_attempt.person_id%TYPE,
84                             p_course_cd               IN igs_en_su_attempt.course_cd%TYPE,
85                             p_course_version          IN igs_en_stdnt_ps_att.version_number%TYPE,
86                             p_start_uoo_id            IN NUMBER,
87                             p_drop_alluoo_ids         IN VARCHAR2,
88                             p_acad_cal_type           IN igs_ca_inst.cal_type%TYPE,
89                             p_acad_ci_sequence_number IN igs_ca_inst.sequence_number%TYPE,
90                             p_load_cal_type           IN igs_ca_inst.cal_type%TYPE,
91                             p_load_sequence_number    IN igs_ca_inst.sequence_number%TYPE,
92                             p_enr_cat                 IN igs_ps_type.enrolment_cat%TYPE,
93                             p_enr_comm                IN VARCHAR2,
94                             p_enr_meth_type           IN igs_en_method_type.enr_method_type%TYPE,
95                             p_dcnt_reason_cd          IN igs_en_dcnt_reasoncd.discontinuation_reason_cd%TYPE,
96                             p_admin_unit_status       IN VARCHAR2,
97                             p_effective_date          IN DATE,
98                             p_deny_warn_coreq         IN VARCHAR2,
99                             p_deny_warn_prereq        IN VARCHAR2,
100                             p_deny_warn_min_cp        IN VARCHAR2,
101                             p_deny_warn_att_type      IN VARCHAR2,
102 			    p_deny_warn_core	      IN VARCHAR2,
103                             p_failed_uoo_ids          OUT NOCOPY VARCHAR2,
104                             p_message                 OUT NOCOPY VARCHAR2,
105                             p_return_status           OUT NOCOPY VARCHAR2) AS
106 
107 
108  -------------------------------------------------------------------------------------------
109   -- Created by  : Basanth Kumar D, Oracle Student Systems Oracle IDC
110   -- Purpose : This proceduere makes min credit,forced att type
111   --           coreq and prereq checks.If it fails the check then a record
112   --           is created in warnings table with message as either deny or warn
113   --           depending on the setup of check and drops the units.Incase of prereq/coreq the
114   --           units that failed the validation  after dropping the units to be dropped
115   --           are passed back as failed units which are dropped in the next iteration of
116   --           the loop.
117   --Change History:
118   --Who         When            What
119   -------------------------------------------------------------------------------------------
120 
121 
122     TYPE c_ref_cursor IS REF CURSOR;
123     c_ref_cur_coreq_prereq c_ref_cursor;
124     v_ref_cur_rec igs_en_su_attempt%ROWTYPE;
125 
126     l_drop_alluoo_ids           VARCHAR2(1000);
127     l_message                   VARCHAR2(200);
128     l_eftsu_total               igs_en_su_attempt.override_eftsu%TYPE;
129     l_credit_points             igs_en_su_attempt.override_enrolled_cp%TYPE;
130     l_total_credit_points       igs_en_su_attempt.override_enrolled_cp%TYPE;
131 
132     l_coreq_failed_uoo_ids      VARCHAR2(1000);
133     l_prereq_failed_uoo_ids     VARCHAR2(1000);
134 
135     l_message_name              VARCHAR2(50);
136 
137     l_att_typ_failed            BOOLEAN;
138     l_uoo_id                    igs_en_su_attempt.uoo_id%TYPE;
139     l_sub_unit                  VARCHAR2(1);
140 
141       -- cursor to get unit details
142     CURSOR get_unit_dtls (p_uoo_id igs_en_su_attempt.uoo_id%TYPE) IS
143     SELECT unit_cd||'/'||unit_class unit_det
144     FROM igs_ps_unit_ofr_opt
145     WHERE uoo_id = p_uoo_id ;
146 
147     l_unit_rec                  get_unit_dtls%ROWTYPE;
148     l_message_icon              VARCHAR2(10);
149     l_rul_text                  VARCHAR2(2000);
150 
151     lv_message_name             VARCHAR2(50);
152     lv_message_name2            VARCHAR2(50);
153     lv_return_type              VARCHAR2(50);
154     l_message_for               VARCHAR2(100);
155     -- bmerugu added for core drop
156     l_deny_warn_core		VARCHAR2(10);
157 
158 
159     NO_AUSL_RECORD_FOUND EXCEPTION;
160     PRAGMA EXCEPTION_INIT(NO_AUSL_RECORD_FOUND , -20010);
161 
162   BEGIN
163 
164      -- cursor to get all uooids with enrolled,invalid status and not in dropped list
165      --modified sqlquery for bug 5037726,sqlid : 14792726
166             OPEN  c_ref_cur_coreq_prereq FOR
167                              'SELECT U.* FROM  IGS_EN_SU_ATTEMPT U, IGS_CA_LOAD_TO_TEACH_V V
168                               WHERE U.person_id = :1
169                               AND U.course_cd = :2
170                               AND U.unit_attempt_status IN  (''ENROLLED'',''INVALID'')
171                               AND U.uoo_id NOT IN ('||p_drop_alluoo_ids||')
172                               AND U.cal_type = V.teach_cal_type
173                               AND U.ci_sequence_number = V.teach_ci_sequence_number
174                               AND V.load_cal_type = :3
175                               AND V.load_ci_sequence_number = :4'
176                               USING p_person_id,p_course_cd,p_load_cal_type,p_load_sequence_number;
177         LOOP
178         -- Loop to get the units failing coreq and prereq validation s vefore dropping the units
179         FETCH c_ref_cur_coreq_prereq INTO v_ref_cur_rec ;
180 
181         EXIT WHEN c_ref_cur_coreq_prereq%NOTFOUND;
182 
183         l_message   := NULL;
184         IF p_deny_warn_coreq IS NOT NULL AND NOT
185           IGS_EN_ELGBL_UNIT.eval_coreq(
186                                         p_person_id                =>  p_person_id,
187                                         p_load_cal_type            =>  p_load_cal_type,
188                                         p_load_sequence_number     =>  p_load_sequence_number,
189                                         p_uoo_id                   =>  v_ref_cur_rec.uoo_id,
190                                         p_course_cd                =>  p_course_cd,
191                                         p_course_version           =>  p_course_version,
192                                         p_message                  =>  l_message,
193                                         p_deny_warn                =>  p_deny_warn_coreq,
194                                         p_calling_obj              => 'DROP') THEN
195 
196 --            l_coreq_failed_units  := l_coreq_failed_units || ',' || v_ref_cur_rec.unit_cd;
197             IF l_coreq_failed_uoo_ids IS NOT NULL THEN
198               l_coreq_failed_uoo_ids := l_coreq_failed_uoo_ids  ||','|| TO_CHAR(v_ref_cur_rec.uoo_id);
199             ELSE
200               l_coreq_failed_uoo_ids := TO_CHAR(v_ref_cur_rec.uoo_id);
201             END IF;
202 
203         END IF;
204 
205         l_message   := NULL;
206         IF p_deny_warn_prereq IS NOT NULL AND NOT
207           IGS_EN_ELGBL_UNIT.eval_prereq(
208                                             p_person_id                =>  p_person_id,
209                                             p_load_cal_type            =>  p_load_cal_type,
210                                             p_load_sequence_number     =>  p_load_sequence_number,
211                                             p_uoo_id                   =>  v_ref_cur_rec.uoo_id,
212                                             p_course_cd                =>  p_course_cd,
213                                             p_course_version           =>  p_course_version,
214                                             p_message                  =>  l_message,
215                                             p_deny_warn                =>  p_deny_warn_prereq,
216                                             p_calling_obj              =>  'DROP') THEN
217 
218 --          l_prereq_failed_units  := l_prereq_failed_units || ',' ||  v_ref_cur_rec.uoo_id;
219           IF l_prereq_failed_uoo_ids IS NOT NULL THEN
220             l_prereq_failed_uoo_ids := l_prereq_failed_uoo_ids||','||TO_CHAR(v_ref_cur_rec.uoo_id);
221           ELSE
222             l_prereq_failed_uoo_ids := TO_CHAR(v_ref_cur_rec.uoo_id);
223           END IF;
224 
225 
226         END IF;
227 
228       END LOOP;
229 
230       CLOSE c_ref_cur_coreq_prereq;
231 
232       l_drop_alluoo_ids := p_drop_alluoo_ids;
233       WHILE l_drop_alluoo_ids IS NOT NULL LOOP
234 
235       l_credit_points := 0;
236 
237       --Check if unit is subordinate and superior is in selection , then   set the l_sub_param to Y
238       --Perform Min CP validation if step is defined. To do this, get the eftsu total before the unit is dropped.
239 
240         --extract the uoo_id
241         IF(instr(l_drop_alluoo_ids,',',1) = 0) THEN
242 
243           l_uoo_id :=TO_NUMBER(l_drop_alluoo_ids);
244 
245         ELSE
246 
247           l_uoo_id := TO_NUMBER(substr(l_drop_alluoo_ids,0,instr(l_drop_alluoo_ids,',',1)-1)) ;
248 
249         END IF;
250 
251         --   Remove the  uoo_id to be  processed
252         IF(instr(l_drop_alluoo_ids,',',1) = 0) THEN
253 
254           l_drop_alluoo_ids := NULL;
255 
256         ELSE
257 
258           l_drop_alluoo_ids :=   substr(l_drop_alluoo_ids,instr(l_drop_alluoo_ids,',',1)+1);
259 
260         END IF; -- end of IF(instr(l_drop_alluoo_ids,',',1) = 0)
261 
262               -- smaddali added this cursor to lock the row , bug#4864437
263               OPEN C_SUA_lock (p_person_id,p_course_cd,l_uoo_id);
264               FETCH C_SUA_lock INTO l_lock_rec;
265               CLOSE C_SUA_lock;
266 
267 
268         l_sub_unit := is_unit_subordinate(p_person_id,
269                                           p_course_cd,
270                                           l_uoo_id,
271                                           p_drop_alluoo_ids);
272 
273         IF p_deny_warn_min_cp  IS NOT NULL THEN
274 
275           l_eftsu_total := igs_en_prc_load.enrp_clc_eftsu_total(
276                                                 p_person_id             => p_person_id,
277                                                 p_course_cd             => p_course_cd ,
278                                                 p_acad_cal_type         => p_acad_cal_type,
279                                                 p_acad_sequence_number  => p_acad_ci_sequence_number,
280                                                 p_load_cal_type         => p_load_cal_type,
281                                                 p_load_sequence_number  => p_load_sequence_number,
282                                                 p_truncate_ind          => 'N',
283                                                 p_include_research_ind  => 'Y'  ,
284                                                 p_key_course_cd         => NULL ,
285                                                 p_key_version_number    => NULL ,
286                                                 p_credit_points         => l_total_credit_points
287                                                 );
288 
289         END IF;
290 
291 	--bmerugu added for core drop
292 	--Evaluate the Allow Core Drop step if setup. If Core Drop fails set the warning message depending on whether the step is deny or warn.  If step is deny, then return.
293         l_message   := NULL;
294         IF p_deny_warn_core  IS NOT NULL AND
295            igs_en_gen_015.eval_core_unit_drop
296                        (
297 			    p_person_id               => p_person_id,
298 			    p_course_cd               => p_course_cd,
299 			    p_uoo_id                  => l_uoo_id,
300 			    p_step_type               => 'DROP_CORE',
301 			    p_term_cal                => p_load_cal_type,
302 			    p_term_sequence_number    => p_load_sequence_number,
303 			    p_deny_warn               => l_deny_warn_core,
304 			    p_enr_method	      => null) = 'FALSE' THEN
305 
306 	   OPEN get_unit_dtls(l_uoo_id);
307 	   FETCH get_unit_dtls INTO l_unit_rec;
308 	   CLOSE get_unit_dtls;
309 	  IF l_deny_warn_core = 'DENY' THEN
310 
311             --Set the message IGS_EN_NO_CORE_REM_CRT and return status to error and return.
312             p_message := 'IGS_EN_SS_SWP_DEL_CORE_FAIL*' || l_unit_rec.unit_det;
313             p_return_status := 'E';
314             RETURN;
315 
316           ELSIF l_deny_warn_core = 'WARN' THEN
317 	    --create a warning record with message_icon set to "W" IGS_EN_NO_CORE_REM_CRT
318             igs_en_drop_units_api.create_ss_warning(
322                                      p_term_ci_sequence_number => p_load_sequence_number,
319                                      p_person_id      => p_person_id,
320                                      p_course_cd      => p_course_cd,
321                                      p_term_cal_type  => p_load_cal_type,
323                                      p_uoo_id => p_start_uoo_id, -- the original unit attempt which started the drop
324                                      p_message_for =>  l_unit_rec.unit_det,
325                                      p_message_icon=> 'W',
326                                      p_message_name => 'IGS_EN_PRCD_DROP_CORE_PAGE',
327                                      p_message_rule_text => NULL,
328                                      p_message_tokens => NULL,
329                                      p_message_action=> NULL,
330                                      p_destination => NULL,
331                                      p_parameters => NULL, --the subordinate for which the warning is created
332                                      p_step_type =>'DROP'
333                                                     );
334 
335           END IF; -- l_deny_warn_core
336 
337         END IF; -- IF l_deny_warn_CORE  IS NOT NULL
338 
339         -- Drop the Unit
340         igs_en_gen_004.enrp_dropall_unit(
341                                         p_person_id          => p_person_id,
342                                         p_cal_type           => p_load_cal_type,
343                                         p_ci_sequence_number => p_load_sequence_number,
344                                         p_dcnt_reason_cd     => p_dcnt_reason_cd,
345                                         p_admin_unit_sta     => p_admin_unit_status,
346                                         p_effective_date     => p_effective_date,
347                                         p_program_cd         => p_course_cd,
348                                         p_uoo_id             => l_uoo_id,
349                                         p_sub_unit           => l_sub_unit
350                                         );
351 
352         --Evaluate the Min CP step if setup. Pass the eftsu calculated in step 2. If Min CP fails set the warning message depending on whether the step is deny or warn.  If step is deny, then return.
353         l_message   := NULL;
354         IF p_deny_warn_min_cp  IS NOT NULL AND
355            NOT igs_en_elgbl_program.eval_min_cp(
356                                                 p_person_id                 =>  p_person_id,
357                                                 p_load_calendar_type        =>  p_load_cal_type,
358                                                 p_load_cal_sequence_number  =>  p_load_sequence_number,
359                                                 p_uoo_id                    =>  l_uoo_id,
360                                                 p_program_cd                =>  p_course_cd,
361                                                 p_program_version           =>  p_course_version,
362                                                 p_message                   =>  l_message,
363                                                 p_deny_warn                 =>  p_deny_warn_min_cp,
364                                                 p_credit_points             =>  l_credit_points ,
365                                                 p_enrollment_category       =>  p_enr_cat,
366                                                 p_comm_type                 =>  p_enr_comm,
367                                                 p_method_type               =>  p_enr_meth_type,
368                                                 p_min_credit_point          =>  l_total_credit_points,
369                                                 p_calling_obj               =>  'DROP') THEN
370 
371           IF p_deny_warn_min_cp = 'DENY' THEN
372 
373             --Set the message IGS_SS_EN_MINIMUM_CP_DENY and return status to error and return.
374             p_message := 'IGS_SS_EN_MINIMUM_CP_DENY';
375             p_return_status := 'E';
376             RETURN;
377 
378           ELSIF p_deny_warn_min_cp = 'WARN' THEN
379 
380             l_message_for := igs_ss_enroll_pkg.enrf_get_lookup_meaning (
381                                                 p_lookup_code => 'FMIN_CRDT',
382                                                 p_lookup_type => 'ENROLMENT_STEP_TYPE_EXT');
383             --create a warning record with message_icon set to "W" IGS_SS_EN_MINIMUM_CP_WARN
384             igs_en_drop_units_api.create_ss_warning(
385                                      p_person_id      => p_person_id,
386                                      p_course_cd      => p_course_cd,
387                                      p_term_cal_type  => p_load_cal_type,
388                                      p_term_ci_sequence_number => p_load_sequence_number,
389                                      p_uoo_id => p_start_uoo_id, -- the original unit attempt which started the drop
390                                      p_message_for =>  l_message_for,
391                                      p_message_icon=> 'W',
392                                      p_message_name => 'IGS_SS_EN_MINIMUM_CP_WARN',
393                                      p_message_rule_text => NULL,
394                                      p_message_tokens => NULL,
395                                      p_message_action=> NULL,
396                                      p_destination => NULL,
397                                      p_parameters => NULL, --the subordinate for which the warning is created
398                                      p_step_type =>'DROP'
399                                                     );
400 
401           END IF; -- l_deny_warn_min_cp
402 
403         END IF; -- IF l_deny_warn_min_cp  IS NOT NULL
404 
405        -- If the Attendance Type validation step has been setup, evaluate the same.
406         l_message   := NULL;
407         IF  p_deny_warn_att_type IS NOT NULL AND
411                                                          p_load_cal_sequence_number  => p_load_sequence_number,
408           NOT igs_en_elgbl_program.eval_unit_forced_type(
409                                                          p_person_id                 => p_person_id,
410                                                          p_load_calendar_type        => p_load_cal_type,
412                                                          p_uoo_id                    => l_uoo_id          ,
413                                                          p_course_cd                 => p_course_cd,
414                                                          p_course_version            => p_course_version,
415                                                          p_message                   => l_message,
416                                                          p_deny_warn                 => p_deny_warn_att_type ,
417                                                          p_enrollment_category       => p_enr_cat,
418                                                          p_comm_type                 => p_enr_comm,
419                                                          p_method_type               => p_enr_meth_type,
420                                                          p_calling_obj               =>  'DROP')  THEN
421 
422           l_att_typ_failed := TRUE;
423 
424             IF l_message  = 'IGS_SS_EN_ATT_TYP_DENY' THEN
425             -- Set the message IGS_SS_EN_ATT_TYP_DENY and return status and return.
426               p_message := 'IGS_SS_EN_ATT_TYP_DENY';
427               p_return_status := 'E';
428 
429               RETURN;
430             ELSIF l_message  = 'IGS_SS_EN_ATT_TYP_WARN' THEN
431 
432              l_message_for := igs_ss_enroll_pkg.enrf_get_lookup_meaning (
433                                                     p_lookup_code => 'FATD_TYPE',
434                                                     p_lookup_type => 'ENROLMENT_STEP_TYPE_EXT');
435             -- Set message to IGS_SS_EN_ATT_TYP_WARN
436             --  Create a warnign record in the warnings table with message_icon as "WARN" , message_for as the lookup_code of the step.
437             --create a warning record with message_icon set to "W" IGS_SS_EN_MINIMUM_CP_WARN
438              igs_en_drop_units_api.create_ss_warning(
439                                  p_person_id      => p_person_id,
440                                  p_course_cd      => p_course_cd,
441                                  p_term_cal_type  => p_load_cal_type,
442                                  p_term_ci_sequence_number => p_load_sequence_number,
443                                  p_uoo_id => p_start_uoo_id, -- the original unit attempt which started the drop
444                                  p_message_for =>  l_message_for,
445                                  p_message_icon=> 'W',
446                                  p_message_name => l_message,
447                                  p_message_rule_text => NULL,
448                                  p_message_tokens => NULL,
449                                  p_message_action=> NULL,
450                                  p_destination => NULL,
451                                  p_parameters => NULL, --the subordinate for which the warning is created
452                                  p_step_type =>'DROP'
453                                         );
454 
455            END IF;
456 
457         END IF ; -- IF l_all_units_for_drop
458 
459       END LOOP; --end of WHILE l_drop_alluoo_ids LOOP
460       --modified sqlquery for bug 5037726,sql id :14792727
461       OPEN  c_ref_cur_coreq_prereq FOR
462       'SELECT U.* FROM  IGS_EN_SU_ATTEMPT U, igs_ca_load_to_teach_v V
463        WHERE U.person_id  = :1
464        AND U.course_cd = :2
465        AND U.unit_attempt_status IN  (''ENROLLED'',''INVALID'')
466        AND U.uoo_id NOT IN ('||p_drop_alluoo_ids||')
467        AND U.cal_type = V.teach_cal_type
468        AND U.ci_sequence_number= V.teach_ci_sequence_number
469        AND V.load_cal_type = :3
470        AND V.load_ci_sequence_number =  :4'
471        USING p_person_id, p_course_cd,p_load_cal_type,p_load_sequence_number;
472 
473       LOOP
474 
475         FETCH c_ref_cur_coreq_prereq INTO v_ref_cur_rec ;
476         EXIT WHEN c_ref_cur_coreq_prereq%NOTFOUND;
477         l_rul_text     := NULL;
478         l_message_name := NULL;
479 
480         IF p_deny_warn_coreq IS NOT NULL AND NOT
481         IGS_EN_ELGBL_UNIT.eval_coreq(
482                                     p_person_id                =>  p_person_id,
483                                     p_load_cal_type            =>  p_load_cal_type,
484                                     p_load_sequence_number     =>  p_load_sequence_number,
485                                     p_uoo_id                   =>  v_ref_cur_rec.uoo_id,
486                                     p_course_cd                =>  p_course_cd,
487                                     p_course_version           =>  p_course_version,
488                                     p_message                  =>  l_rul_text, -- rule text is returned
489                                     p_deny_warn                =>  p_deny_warn_coreq,
490                                     p_calling_obj              =>   'DROP') THEN
491 
492           --Check if the coreq step is set to deny or warn .
493           IF  (l_coreq_failed_uoo_ids IS NULL OR  INSTR(','||l_coreq_failed_uoo_ids||',' , ','||v_ref_cur_rec.uoo_id||',') = 0) THEN
494 
495             IF p_deny_warn_coreq = 'DENY' THEN
496 
497               l_message_icon := 'D';
498               l_message_name := 'IGS_SS_EN_COREQ_DRP_DENY';
499 
500               IF  p_failed_uoo_ids IS NOT NULL THEN
501 
502                 p_failed_uoo_ids      := p_failed_uoo_ids  ||','|| TO_CHAR(v_ref_cur_rec.uoo_id);
503 
504               ELSE
505 
509 
506                 p_failed_uoo_ids      :=  TO_CHAR(v_ref_cur_rec.uoo_id);
507 
508               END IF;
510             ELSIF p_deny_warn_coreq = 'WARN' THEN
511 
512               l_message_icon := 'W';
513               l_message_name := 'IGS_SS_EN_COREQ_DRP_WARN';
514 
515             END IF;
516 
517 
518             OPEN get_unit_dtls(v_ref_cur_rec.uoo_id);
519             FETCH get_unit_dtls INTO l_unit_rec;
520             CLOSE get_unit_dtls;
521 
522             igs_en_drop_units_api.create_ss_warning(
523                             p_person_id => p_person_id,
524                             p_course_cd => p_course_cd,
525                             p_Term_cal_type=>p_load_cal_type,
526                             p_term_ci_sequence_number => p_load_sequence_number,
527                             p_uoo_id => p_start_uoo_id,
528                             p_message_for => l_unit_rec.unit_det,
529                             p_message_icon=> l_message_icon,
530                             p_message_name =>l_message_name,
531                             p_message_tokens=> NULL,
532                             p_message_rule_text => l_rul_text,
533                             p_message_action=> NULL,
534                             p_destination => NULL,
535                             p_parameters => v_ref_cur_rec.uoo_id,--uoo_id of the unit for which the warnign record is being created null
536                             p_step_type =>'DROP');
537           END IF; -- end of  IF  (l_coreq_failed_uoo_ids IS NULL
538 
539         END IF; -- end of IF l_deny_warn_coreq IS NOT NULL
540 
541 
542         -- Do the same checks for Pre-Req rule
543 
544          l_rul_text     := NULL;
545          l_message_name := NULL;
546 
547         IF p_deny_warn_prereq IS NOT NULL AND
548            NOT IGS_EN_ELGBL_UNIT.eval_prereq(
549                                     p_person_id                =>  p_person_id,
550                                     p_load_cal_type            =>  p_load_cal_type,
551                                     p_load_sequence_number     =>  p_load_sequence_number,
552                                     p_uoo_id                   =>  v_ref_cur_rec.uoo_id,
553                                     p_course_cd                =>  p_course_cd,
554                                     p_course_version           =>  p_course_version,
555                                     p_message                  =>  l_rul_text,  -- rule text is returned
556                                     p_deny_warn                =>  p_deny_warn_prereq,
557                                     p_calling_obj              =>  'DROP') THEN
558 
559           -- Append to failed uoo_ids if step is set to deny.
560           IF   (l_prereq_failed_uoo_ids IS NULL OR INSTR(','||l_prereq_failed_uoo_ids||',' , ','||v_ref_cur_rec.uoo_id||',' ) = 0) THEN
561 
562             IF p_deny_warn_prereq = 'DENY' THEN
563 
564               l_message_icon := 'D';
568 
565               l_message_name := 'IGS_SS_EN_PREREQ_DRP_DENY';
566 
567               IF  p_failed_uoo_ids IS NOT NULL THEN
569                 p_failed_uoo_ids      := p_failed_uoo_ids  ||','|| TO_CHAR(v_ref_cur_rec.uoo_id);
570 
571               ELSE
572 
573                 p_failed_uoo_ids      :=  TO_CHAR(v_ref_cur_rec.uoo_id);
574 
575               END IF;
576 
577             ELSE
578 
579               l_message_icon := 'W';
580               l_message_name := 'IGS_SS_EN_PREREQ_DRP_WARN';
581 
582             END IF;
583 
584 
585             OPEN get_unit_dtls(v_ref_cur_rec.uoo_id);
586             FETCH get_unit_dtls INTO l_unit_rec;
587             CLOSE get_unit_dtls;
588 
589             -- Create the warning record.
590               igs_en_drop_units_api.create_ss_warning(
591                                             p_person_id => p_person_id,
592                                             p_course_cd => p_course_cd,
593                                             p_Term_cal_type=>p_load_cal_type,
594                                             p_term_ci_sequence_number => p_load_sequence_number,
595                                             p_uoo_id => p_start_uoo_id,
596                                             p_message_for => l_unit_rec.unit_det,
597                                             p_message_icon=> l_message_icon,
598                                             p_message_name =>l_message_name,
599                                             p_message_tokens=> NULL,
600                                             p_message_rule_text => l_rul_text,
601                                             p_message_action=> NULL,
602                                             p_destination => NULL,
603                                             p_parameters => v_ref_cur_rec.uoo_id,--uoo_id of the unit for which the warnign record is being created null
604                                             p_step_type =>'DROP');
605           END IF; -- IF   (l_prereq_failed_uoo_ids IS NULL
606 
607         END IF; -- IF l_deny_warn_prereq IS NOT NULL
608 
609       END LOOP; -- end of loop for cursor c_ref_cur_coreq_prereq
610 
611       CLOSE c_ref_cur_coreq_prereq;
612 
613       --Now implement the encumbrance checks for required untis.
614       IF NOT IGS_EN_VAL_ENCMB.enrp_val_enr_encmb(p_person_id => p_person_id,
615                                          p_course_cd => p_course_cd,
616                                          p_cal_type => p_load_cal_type,
617                                          p_ci_sequence_number => p_load_sequence_number,
618                                          p_message_name => lv_message_name ,
619                                          p_message_name2 => lv_message_name2,
620                                          p_return_type => lv_return_type,
621                                          p_effective_dt => NULL -- default value, it will be calculated internally based on the census date
622                                          )   THEN
623 
624        -- Check for the messages returned by this function in lv_message_name and lv_message_name2. If these messages relate to the required units check then overwrite these messages with messages that have been defined for self service diplay.
625 
626         IF  lv_message_name = 'IGS_EN_PRSN_NOTENR_REQUIRE' OR lv_message_name2 = 'IGS_EN_PRSN_NOTENR_REQUIRE' THEN
627 
628         -- Override message with 'IGS_EN_REQ_UNIT_CANNOT_DROP'
629           p_message := 'IGS_EN_REQ_UNIT_CANNOT_DROP';
630         END IF;
631 
632         p_return_status := 'E';
633         RETURN;
634 
635       END IF; -- end of IF NOT IGS_EN_VAL_ENCMB.enrp_val_enr_encmb
636 
637   EXCEPTION
638 
639     -- To handle user defined exception raised when adminstrative unit status cannot be detremined
640     WHEN NO_AUSL_RECORD_FOUND THEN
641       RAISE NO_AUSL_RECORD_FOUND;
642 
643     WHEN APP_EXCEPTION.APPLICATION_EXCEPTION THEN
644       RAISE;
645 
646     WHEN OTHERS THEN
647 
648       Fnd_Message.Set_Name('IGS','IGS_GE_UNHANDLED_EXP');
649       FND_MESSAGE.SET_TOKEN('NAME', 'IGS_EN_DROP_UNITS_API.drop_units');
650       IGS_GE_MSG_STACK.ADD;
651       IF (FND_LOG.LEVEL_UNEXPECTED >= g_debug_level ) THEN
652             FND_LOG.STRING(fnd_log.level_unexpected, 'igs.patch.115.sql.igs_en_drop_units_api.drop_units :',SQLERRM);
653       END IF;
654       RAISE;
655 
656   END drop_units ;
657 
658 
659 
660   PROCEDURE drop_student_unit_attempts(
661                                      p_person_id              IN igs_en_su_attempt.person_id%TYPE,
662                                      p_course_cd              IN igs_en_su_attempt.course_cd%TYPE,
663                                      p_course_version         IN igs_en_stdnt_ps_att.version_number%TYPE,
664                                      p_start_uoo_id           IN NUMBER,
665                                      p_drop_uoo_ids           IN VARCHAR2,
666                                      p_acad_cal_type          IN igs_ca_inst.cal_type%TYPE,
667                                      p_acad_ci_sequence_number IN igs_ca_inst.sequence_number%TYPE,
668                                      p_load_cal_type          IN igs_ca_inst.cal_type%TYPE,
669                                      p_load_sequence_number   IN igs_ca_inst.sequence_number%TYPE,
670                                      p_enr_cat                IN igs_ps_type.enrolment_cat%TYPE,
671                                      p_enr_comm               IN VARCHAR2,
672                                      p_enr_meth_type          IN igs_en_method_type.enr_method_type%TYPE,
673                                      p_dcnt_reason_cd         IN igs_en_dcnt_reasoncd.discontinuation_reason_cd%TYPE,
674                                      p_admin_unit_status      IN VARCHAR2,
678                                      p_deny_warn_min_cp       IN VARCHAR2,
675                                      p_effective_date         IN DATE,
676                                      p_deny_warn_coreq        IN VARCHAR2,
677                                      p_deny_warn_prereq       IN VARCHAR2,
679                                      p_deny_warn_att_type     IN VARCHAR2,
680 				     p_deny_warn_core	      IN VARCHAR2,
681                                      p_failed_uoo_ids         OUT NOCOPY VARCHAR2,
682                                      p_uooids_dropped         OUT NOCOPY VARCHAR2,
683                                      p_message                OUT NOCOPY VARCHAR2,
684                                      p_return_status          OUT NOCOPY VARCHAR2) AS
685 
686   -------------------------------------------------------------------------------------------
687   -- Created by  : Basanth Kumar D, Oracle Student Systems Oracle IDC
688   -- Purpose : This procedure reorders the units with subordantes first
689   --  and cheks whether all units in enrolled,waitlisted and invalid are to be dropped
690   --  or apart from duplicates all the units are to be dropped then  just drop the units
691   --  without making any validations else call drop units which validates and drops
692   --Change History:
693   --Who         When            What
694   -------------------------------------------------------------------------------------------
695 
696 
697 
698     l_drop_alluoo_ids   VARCHAR2(1000);
699     l_sub_drop_uoo_ids  VARCHAR2(1000);
700     l_nonsub_uoo_ids    VARCHAR2(1000);
701 
702     TYPE c_ref_cursor IS REF CURSOR;
703     c_chk_units c_ref_cursor;
704     c_ref_only_dup c_ref_cursor;
705     c_chk_is_sub c_ref_cursor;
706     v_ref_cur_rec igs_en_su_attempt%ROWTYPE;
707 
708     l_all_units_for_drop BOOLEAN;
709 
710     l_credit_points        igs_en_su_attempt.override_enrolled_cp%TYPE;
711     l_uoo_id               igs_en_su_attempt.uoo_id%TYPE;
712     l_sub_unit             VARCHAR2(1);
713 
714     l_enc_message_name              VARCHAR2(2000);
715     l_app_short_name                VARCHAR2(100);
716     l_msg_index                     NUMBER;
717     l_message_name                  VARCHAR2(4000);
718 
719     NO_AUSL_RECORD_FOUND EXCEPTION;
720     PRAGMA EXCEPTION_INIT(NO_AUSL_RECORD_FOUND , -20010);
721 
722   BEGIN
723 
724     l_credit_points := 0;
725     igs_en_drop_units_api.reorder_drop_units (
726                                                     p_person_id => p_person_id ,
727                                                     p_course_cd => p_course_cd,
728                                                     p_start_uoo_id => p_start_uoo_id,
729                                                     p_load_cal_type => p_load_cal_type,
730                                                     p_load_ci_seq_num => p_load_sequence_number,
731                                                     p_selected_uoo_ids => p_drop_uoo_ids,  ---  uooids that are to be dropped
732                                                     p_ret_all_uoo_ids => l_drop_alluoo_ids, -- uooids that are to be dropping after adding subordinate units
733                                                     p_ret_sub_uoo_ids => l_sub_drop_uoo_ids, -- retunrs the subordinate uooids if any in the uooids to be dropped
734                                                     p_ret_nonsub_uoo_ids => l_nonsub_uoo_ids
735                                                     );
736     -- assign the uooids to be dropped to the out parameter
737     p_uooids_dropped := l_drop_alluoo_ids;
738 
739     -- check whether all enrolled,invalid,wsitlisted units for that person,course are selected,
740     --in which case, just delete all units w/o checking cp or coreq requirements.
741     --modified sqlquery for bug 5037726 ,sql id :14792729
742 
743     OPEN c_chk_units FOR
744                             'SELECT U.* FROM IGS_EN_SU_ATTEMPT U
745                              WHERE person_id =:1
746                              AND course_cd = :2
747                              AND unit_attempt_status IN  (''ENROLLED'',''INVALID'',''WAITLISTED'')
748                              AND (cal_type,ci_sequence_number) IN
749                                                                   (SELECT teach_cal_type,teach_ci_sequence_number
750                                                                    FROM igs_ca_load_to_teach_v
751                                                                    WHERE load_cal_type = :3
752                                                                    AND load_ci_sequence_number =:4 )
753                                                                    AND uoo_id NOT IN('||l_drop_alluoo_ids||')'
754                              USING p_person_id, p_course_cd, p_load_cal_type, p_load_sequence_number ;
755 
756     FETCH c_chk_units INTO v_ref_cur_rec ;
757 
758     l_all_units_for_drop := FALSE;
759     IF c_chk_units%NOTFOUND THEN
760 
761         l_all_units_for_drop := TRUE;
762 
763     END IF;
764     CLOSE c_chk_units;
765 
766 
767     IF NOT l_all_units_for_drop THEN
768       -- Even if all unit attempts except duplicates are selected for drop then do
769       -- not perform any validations. So that we do not get any min cp or
770       -- attendance type validation fialures.
771       --modified sqlquery for bug 5037726
772       OPEN c_ref_only_dup FOR
773                               'SELECT U.* FROM  IGS_EN_SU_ATTEMPT U
774                                WHERE person_id =:1
775                                AND course_cd = :2
776                                AND unit_attempt_status <> ''DUPLICATE''
777                                AND (cal_type,ci_sequence_number) IN
778                                                                     (SELECT teach_cal_type,teach_ci_sequence_number
779                                                                      FROM igs_ca_load_to_teach_v
783                                USING p_person_id, p_course_cd, p_load_cal_type, p_load_sequence_number;
780                                                                      WHERE load_cal_type = :3
781                                                                      AND load_ci_sequence_number =:4 )
782                                AND uoo_id IN('||l_drop_alluoo_ids||')'
784       FETCH c_ref_only_dup INTO v_ref_cur_rec ;
785 
786       l_all_units_for_drop := FALSE;
787       IF c_ref_only_dup%NOTFOUND THEN
788 
789         -- except duplicates units all other units are selected for drop
790         l_all_units_for_drop := TRUE;
791 
792       END IF;
793 
794       CLOSE c_ref_only_dup;
795 
796     END IF; -- end of IF NOT l_all_units_for_drop
797 
798     -- if only duplicates are not selected for drop the drop without any validations
799     IF l_all_units_for_drop THEN
800 
801       WHILE l_drop_alluoo_ids IS NOT NULL LOOP
802 
803         l_credit_points := 0;
804 
805         --extract the uoo_id
806         IF(instr(l_drop_alluoo_ids,',',1) = 0) THEN
807 
808           l_uoo_id :=TO_NUMBER(l_drop_alluoo_ids);
809 
810         ELSE
811 
812           l_uoo_id := TO_NUMBER(substr(l_drop_alluoo_ids,0,instr(l_drop_alluoo_ids,',',1)-1)) ;
813 
814         END IF;
815 
816         --   Remove the  uoo_id that will be processed
817         IF(instr(l_drop_alluoo_ids,',',1) = 0) THEN
818 
819           l_drop_alluoo_ids := NULL;
820 
821         ELSE
822 
823           l_drop_alluoo_ids :=   substr(l_drop_alluoo_ids,instr(l_drop_alluoo_ids,',',1)+1);
824 
825         END IF; -- end of IF(instr(l_drop_alluoo_ids,',',1) = 0)
826 
827           -- smaddali added this cursor to lock the row , bug#4864437
828           OPEN C_SUA_lock (p_person_id,p_course_cd,l_uoo_id);
829           FETCH C_SUA_lock INTO l_lock_rec;
830           CLOSE C_SUA_lock;
831 
832         -- Set the parameter to  indicate if unit is subordinate
833         l_sub_unit := 'N';
834 
835         IF l_sub_drop_uoo_ids IS NOT NULL THEN
836 
837           l_sub_unit := is_unit_subordinate(p_person_id,
838                                             p_course_cd,
839                                             l_uoo_id,
840                                             p_uooids_dropped);    -- use the entire set uooids that will be dropped
841 
842 
843         END IF;   -- end of IF l_sub_drop_uoo_ids IS NOT NULL
844 
845         igs_en_gen_004.enrp_dropall_unit(
846                                                  p_person_id          => p_person_id,
847                                                  p_cal_type           => p_load_cal_type,
848                                                  p_ci_sequence_number => p_load_sequence_number,
849                                                  p_dcnt_reason_cd     => p_dcnt_reason_cd,
850                                                  p_admin_unit_sta     => p_admin_unit_status,
851                                                  p_effective_date     => p_effective_date,
852                                                  p_program_cd         => p_course_cd,
853                                                  p_uoo_id             => l_uoo_id,
854                                                  p_sub_unit           => l_sub_unit);
855 
856 
857       END LOOP; -- end of loop
858 
859     -- if not all the enrolled,invalid,wailsited units are not in list of units to be dropped or
860     -- apart from duplicate units their are units which are not their in list of dropped units
861     -- then validate prereq,coreq,min_cp,forced att type and if successful then drop units
862     ELSE
863 
864 
865       drop_units(
866                 p_person_id,
867                 p_course_cd,
868                 p_course_version,
869                 p_start_uoo_id,
870                 l_drop_alluoo_ids,
871                 p_acad_cal_type,
872                 p_acad_ci_sequence_number,
873                 p_load_cal_type,
874                 p_load_sequence_number,
875                 p_enr_cat,
876                 p_enr_comm,
877                 p_enr_meth_type,
878                 p_dcnt_reason_cd,
879                 p_admin_unit_status,
880                 p_effective_date,
881                 p_deny_warn_coreq,
882                 p_deny_warn_prereq,
883                 p_deny_warn_min_cp,
884                 p_deny_warn_att_type,
885 		p_deny_warn_core,
886                 p_failed_uoo_ids,
887                 p_message,
888                 p_return_status);
889 
890         IF p_return_status = 'E' THEN
891 
892           RETURN;
893 
894         END IF;
895 
896 
897 
898     END IF;  -- end of  IF l_all_units_for_drop THEN
899 
900 
901   EXCEPTION
902 
903     -- To handle user defined exception raised when adminstrative unit status cannot be detremined
904     WHEN NO_AUSL_RECORD_FOUND THEN
905       RAISE NO_AUSL_RECORD_FOUND;
906 
907     WHEN APP_EXCEPTION.APPLICATION_EXCEPTION THEN
908       RAISE;
909 
910     WHEN OTHERS THEN
911       Fnd_Message.Set_Name('IGS','IGS_GE_UNHANDLED_EXP');
912       FND_MESSAGE.SET_TOKEN('NAME', 'IGS_EN_DROP_UNITS_API.drop_student_unit_attempts');
913       IGS_GE_MSG_STACK.ADD;
914       IF (FND_LOG.LEVEL_UNEXPECTED >= g_debug_level ) THEN
915             FND_LOG.STRING(fnd_log.level_unexpected, 'igs.patch.115.sql.igs_en_drop_units_api.drop_student_unit_attempts :',SQLERRM);
916       END IF;
917       RAISE;
918 
919   END drop_student_unit_attempts;
920 
921 
925                                  p_start_uoo_id         IN igs_en_su_attempt.uoo_id%TYPE,
922   PROCEDURE reorder_drop_units(
923                                  p_person_id            IN igs_en_su_attempt.person_id%TYPE,
924                                  p_course_cd            IN igs_en_su_attempt.course_cd%TYPE,
926                                  p_load_cal_type        IN igs_ca_inst.cal_type%TYPE,
927                                  p_load_ci_seq_num      IN igs_ca_inst.sequence_number%TYPE,
928                                  p_selected_uoo_ids     IN VARCHAR2,
929                                  p_ret_all_uoo_ids      OUT NOCOPY VARCHAR2,
930                                  p_ret_sub_uoo_ids      OUT NOCOPY VARCHAR2,
931                                  p_ret_nonsub_uoo_ids   OUT NOCOPY VARCHAR2
932                                )  AS
933 
934   -------------------------------------------------------------------------------------------
935   -- Created by  : Basanth Kumar D, Oracle Student Systems Oracle IDC
936   -- Purpose : This procedure adds  if any subordinates of the units to be dropped are not inlcuded
937   --  in the drop list and reorders them with subordinates followed by superior units.
938   --Change History:
939   --Who         When            What
940   -------------------------------------------------------------------------------------------
941 
942 
943 
944 -- cursor to get unit details
945     CURSOR get_unit_dtls (p_uoo_id igs_en_su_attempt.uoo_id%TYPE) IS
946     SELECT unit_cd||'/'||unit_class unit_det
947     FROM igs_ps_unit_ofr_opt
948     WHERE uoo_id = p_uoo_id ;
949 
950     TYPE c_ref_cursor IS REF CURSOR;
951     c_chk_sub c_ref_cursor;
952 
953     l_unit_section      get_unit_dtls%ROWTYPE;
954     l_grep_uoo_ids      VARCHAR2(2000);
955     l_selected_uoo_ids  VARCHAR2(3000);
956     l_sub_uooid         igs_ps_unit_ofr_opt.uoo_id%TYPE;
957     l_unit_cd           igs_ps_unit_ofr_opt.unit_cd%TYPE;
958     l_unit_class        igs_ps_unit_ofr_opt.unit_class%TYPE;
959     l_sup_uooid         igs_ps_unit_ofr_opt.sup_uoo_id%TYPE;
960 
961   BEGIN
962 
963     --modified sql query for bug 5037726,sqlid:14792730
964     OPEN c_chk_sub FOR
965    'SELECT uoo.uoo_id sub_uoo_id, uoo.unit_cd, uoo.unit_class, uoo.sup_uoo_id
966     FROM igs_ps_unit_ofr_opt uoo
967     WHERE uoo.sup_uoo_id  IN ('||p_selected_uoo_ids||')
968     AND uoo.RELATION_TYPE  = ''SUBORDINATE''
969     AND uoo.uoo_id IN
970                     ( SELECT uoo_id FROM igs_en_su_attempt
971                       WHERE person_id =  :1
972                       AND course_cd =  :2
973                       AND cal_type = uoo.cal_type
974                       AND ci_sequence_number = uoo.ci_sequence_number
975                       AND unit_Attempt_status NOT IN (''DROPPED'', ''DISCONTIN'')
976                       AND uoo_id NOT IN ('||p_selected_uoo_ids||')
977                     )' USING p_person_id,p_course_cd;
978 
979 
980 
981     LOOP
982 
983       FETCH c_chk_sub INTO l_sub_uooid,l_unit_cd,l_unit_class,l_sup_uooid;
984 
985       EXIT WHEN c_chk_sub%NOTFOUND;
986 
987       OPEN get_unit_dtls(l_sup_uooid);
988 
989       FETCH get_unit_dtls INTO l_unit_section;
990 
991       IF get_unit_dtls%FOUND THEN
992 
993         IF  l_grep_uoo_ids IS NULL THEN
994 
995           l_grep_uoo_ids := l_sub_uooid;
996 
997         ELSE
998 
999           l_grep_uoo_ids := l_grep_uoo_ids||','||l_sub_uooid;
1000 
1001         END IF;
1002 
1003         igs_en_drop_units_api.create_ss_warning(
1004                                                  p_person_id      => p_person_id,
1005                                                  p_course_cd      => p_course_cd,
1006                                                  p_term_cal_type  => p_load_cal_type,
1007                                                  p_term_ci_sequence_number => p_load_ci_seq_num,
1008                                                  p_uoo_id => p_start_uoo_id, -- the original unit attempt which started the drop
1009                                                  p_message_for => l_unit_cd || '/'|| l_unit_class ,
1010                                                  p_message_icon=> 'D',
1011                                                  p_message_name => 'IGS_EN_WILL_DROP_SUP',
1012                                                  p_message_rule_text => NULL,
1013                                                  p_message_tokens => 'UNIT_CD:'|| l_unit_section.unit_det||';',
1014                                                  p_message_action=> NULL,
1015                                                  p_destination => NULL,
1016                                                  p_parameters => NULL,
1017                                                  p_step_type =>'DROP'
1018                                                 );
1019 
1020 
1021       END IF;
1022 
1023       CLOSE get_unit_dtls;
1024 
1025     END LOOP;
1026 
1027     IF l_grep_uoo_ids IS NOT NULL THEN
1028       l_selected_uoo_ids    := p_selected_uoo_ids ||','|| l_grep_uoo_ids;
1029     ELSE
1030       l_selected_uoo_ids    := p_selected_uoo_ids;
1031     END IF;
1032 
1033 
1034     IGS_SS_EN_WRAPPERS.enrp_chk_del_sub_units (
1035                                     p_person_id           => p_person_id ,
1036                                     p_course_cd           => p_course_cd,
1037                                     p_load_cal_type       => p_load_cal_type,
1038                                     p_load_ci_seq_num     => p_load_ci_seq_num,
1039                                     p_selected_uoo_ids    => l_selected_uoo_ids,
1040                                     p_ret_all_uoo_ids     => p_ret_all_uoo_ids,
1044                                 );
1041                                     p_ret_sub_uoo_ids     => p_ret_sub_uoo_ids,
1042                                     p_ret_nonsub_uoo_ids  => p_ret_nonsub_uoo_ids,
1043                                     p_delete_flag         => 'N'
1045 
1046 
1047     IF  p_ret_all_uoo_ids IS NULL THEN
1048 
1049       p_ret_all_uoo_ids :=  l_selected_uoo_ids;
1050 
1051     END IF;
1052 
1053     RETURN;
1054 
1055   EXCEPTION
1056     WHEN APP_EXCEPTION.APPLICATION_EXCEPTION THEN
1057       RAISE;
1058 
1059     WHEN OTHERS THEN
1060       Fnd_Message.Set_Name('IGS','IGS_GE_UNHANDLED_EXP');
1061       FND_MESSAGE.SET_TOKEN('NAME', 'IGS_EN_DROP_UNITS_API.reorder_drop_units');
1062       IGS_GE_MSG_STACK.ADD;
1063       IF (FND_LOG.LEVEL_UNEXPECTED >= g_debug_level ) THEN
1064             FND_LOG.STRING(fnd_log.level_unexpected, 'igs.patch.115.sql.igs_en_drop_units_api.reorder_drop_units :',SQLERRM);
1065       END IF;
1066       ROLLBACK;
1067       RAISE;
1068 
1069 
1070   END reorder_drop_units;
1071 
1072 
1073   PROCEDURE create_ss_warning (
1074             p_person_id                 IN igs_en_su_attempt.person_id%TYPE,
1075             p_course_cd                 IN igs_en_su_attempt.course_cd%TYPE,
1076             p_term_cal_type             IN igs_ca_inst.cal_type%TYPE,
1077             p_term_ci_sequence_number   IN igs_ca_inst.sequence_number%TYPE,
1078             p_uoo_id                    IN igs_en_su_attempt.uoo_id%TYPE,
1079             p_message_for               IN IGS_EN_STD_WARNINGS.message_for%TYPE,
1080             p_message_icon              IN IGS_EN_STD_WARNINGS.message_icon%TYPE,
1081             p_message_name              IN IGS_EN_STD_WARNINGS.message_name%TYPE,
1082             p_message_rule_text         IN VARCHAR2,
1083             p_message_tokens            IN VARCHAR2,
1084             p_message_action            IN VARCHAR2,
1085             p_destination               IN IGS_EN_STD_WARNINGS.destination%TYPE,
1086             p_parameters                IN IGS_EN_STD_WARNINGS.p_parameters%TYPE,
1087             p_step_type                 IN IGS_EN_STD_WARNINGS.step_type%TYPE) AS
1088 
1089     PRAGMA AUTONOMOUS_TRANSACTION;
1090 
1091     -------------------------------------------------------------------------------------------
1092   -- Created by  : Basanth Kumar D, Oracle Student Systems Oracle IDC
1093   -- Purpose : This procedure creates a record in warnings table after getting the relevant data
1094   --Change History:
1095   --Who         When            What
1096   -------------------------------------------------------------------------------------------
1097 
1098 
1099 
1100     l_token_set         VARCHAR2(1000);
1101     l_token             VARCHAR2(100);
1102     l_token_value       VARCHAR2(100);
1103     l_message_text      VARCHAR2(2000);
1104     l_row_id            VARCHAR2(30);
1105     x_warning_id        NUMBER;
1106     l_message_tokens    VARCHAR2(1000);
1107     -- cursor to get the record using unique key
1108       -- Unique key for
1109       -- DROP step :             person_id,course_cd,p_term_cal_type,p_term_ci_sequence_number,step_type,uoo_id,p_message_for,p_message_name
1110       -- PERSON,PROGRAM steps :  person_id,course_cd,p_term_cal_type,p_term_ci_sequence_number,step_type,p_message_for
1111       -- UNIT step :             person_id,course_cd,p_term_cal_type,p_term_ci_sequence_number,step_type,uoo_id,message_name
1112 
1113     CURSOR c_rec_exists IS
1114     SELECT ROWID,warn.*
1115     FROM igs_en_std_warnings warn
1116     WHERE person_id = p_person_id
1117     AND course_cd = p_course_cd
1118     AND term_cal_type = p_term_cal_type
1119     AND term_ci_sequence_number = p_term_ci_sequence_number
1120     AND step_type = p_step_type
1121     AND (
1122                 (p_step_type = 'DROP' AND uoo_id = p_uoo_id AND message_for = p_message_for AND message_name = p_message_name)
1123                 OR (p_step_type IN  ('PROGRAM','PERSON') AND message_for = p_message_for)
1124                 OR (p_step_type = 'UNIT' AND uoo_id = p_uoo_id    AND message_name = p_message_name)
1125             );
1126 
1127 
1128 
1129     l_warn_rec    c_rec_exists%ROWTYPE;
1130 
1131 
1132     BEGIN
1133 
1134       FND_MESSAGE.SET_NAME('IGS',p_message_name);
1135 
1136       l_message_tokens := p_message_tokens;
1137       WHILE l_message_tokens IS NOT NULL LOOP
1138 
1139 
1140           l_token_set := substr(l_message_tokens, 0, instr(l_message_tokens,';')-1);
1141           l_token := substr(l_token_set, 0, instr(l_token_set, ':')-1);
1142           l_token_value := substr(l_token_set, instr(l_token_set, ':')+1);
1143           FND_MESSAGE.SET_TOKEN (l_token, l_token_value);
1144 
1145           l_message_tokens := substr(l_message_tokens, instr(l_message_tokens,';')+1);
1146 
1147 
1148       END LOOP;
1149 
1150       l_message_text := FND_MESSAGE.GET();
1151 
1152       IF p_message_rule_text IS NOT NULL THEN
1153 
1154         l_message_text := l_message_text || p_message_rule_text;
1155 
1156       END IF;
1157 
1158       OPEN c_rec_exists;
1159       FETCH c_rec_exists INTO l_warn_rec;
1160       IF c_rec_exists%NOTFOUND THEN
1161 
1162                IGS_EN_STD_WARNINGS_PKG.INSERT_ROW (
1163                               x_rowid                     =>  l_row_id,
1164                               x_warning_id                =>  x_warning_id,
1165                               x_person_id                 =>  p_person_id,
1166                               x_course_cd                 =>  p_course_cd,
1167                               x_uoo_id                    =>  p_uoo_id,
1168                               x_term_cal_type             =>  p_term_cal_type,
1169                               x_term_ci_sequence_number   =>  p_term_ci_sequence_number,
1170                               x_message_for               =>  p_message_for,
1174                               x_message_action            =>  p_message_action,
1171                               x_message_icon              =>  p_message_icon,
1172                               x_message_name              =>  p_message_name,
1173                               x_message_text              =>  l_message_text,
1175                               x_destination               =>  p_destination,
1176                               x_p_parameters              =>  p_parameters,
1177                               x_step_type                 =>  p_step_type,
1178                               x_session_id                =>  igs_en_add_units_api.g_ss_session_id,
1179                               x_mode                      =>  'R'     );
1180        ELSE -- update the row
1181                 IGS_EN_STD_WARNINGS_PKG.UPDATE_ROW (
1182                                     x_rowid                     =>  l_warn_rec.rowid,
1183                                     x_warning_id                => l_warn_rec.warning_id,
1184                                     x_person_id                 =>   p_person_id,
1185                                     x_course_cd                 =>   p_course_cd,
1186                                     x_uoo_id                    =>  p_uoo_id,
1187                                     x_term_cal_type             =>  p_term_cal_type,
1188                                     x_term_ci_sequence_number   =>  p_term_ci_sequence_number,
1189                                     x_message_for               =>  p_message_for,
1190                                     x_message_icon              =>  p_message_icon,
1191                                     x_message_name              =>  p_message_name,
1192                                     x_message_text              =>  l_message_text,
1193                                     x_message_action            =>  p_message_action,
1194                                     x_destination               =>  p_destination,
1195                                     x_p_parameters              =>  p_parameters,
1196                                     x_step_type                 =>  p_step_type,
1197                                     x_session_id                =>  igs_en_add_units_api.g_ss_session_id,
1198                                     x_mode                      =>  'R'    );
1199 
1200        END IF;
1201        COMMIT;
1202 
1203     EXCEPTION
1204 
1205       WHEN APP_EXCEPTION.APPLICATION_EXCEPTION THEN
1206         RAISE;
1207 
1208       WHEN OTHERS THEN
1209 
1210         Fnd_Message.Set_Name('IGS','IGS_GE_UNHANDLED_EXP');
1211         FND_MESSAGE.SET_TOKEN('NAME', 'IGS_EN_DROP_UNITS_API.create_ss_warning');
1212         IGS_GE_MSG_STACK.ADD;
1213         IF (FND_LOG.LEVEL_UNEXPECTED >= g_debug_level ) THEN
1214               FND_LOG.STRING(fnd_log.level_unexpected, 'igs.patch.115.sql.igs_en_drop_units_api.create_ss_warning :',SQLERRM);
1215         END IF;
1216         ROLLBACK;
1217         RAISE;
1218 
1219     END create_ss_warning;
1220 
1221     FUNCTION get_aus_desc(p_token IN VARCHAR2)
1222     RETURN VARCHAR2 AS
1223       l_token VARCHAR2(2000);
1224       l_token_desc VARCHAR2(2000);
1225       l_stmt VARCHAR2(2000);
1226 
1227       TYPE c_ref_cur_typ IS REF CURSOR;
1228       c_ref_cur c_ref_cur_typ;
1229 
1230       l_description igs_ad_adm_unit_stat.description%TYPE;
1231 
1232     BEGIN
1233       l_token_desc := NULL;
1234       l_token :=  '''' || REPLACE (p_token, ',',''',''') || '''';
1235 
1236       l_stmt := 'SELECT description
1237                 FROM igs_ad_adm_unit_stat_v
1238                 WHERE unit_attempt_status = ''DISCONTIN''
1239                 AND closed_ind = ''N''
1240                 AND administrative_unit_status IN (' || l_token || ')';
1241 
1242 
1243       OPEN c_ref_cur FOR l_stmt;
1244 
1245       LOOP
1246         FETCH c_ref_cur INTO l_description;
1247         EXIT WHEN c_ref_cur%NOTFOUND ;
1248 
1249         IF l_token_desc IS NULL THEN
1250           l_token_desc := l_description;
1251         ELSE
1252           l_token_desc := l_token_desc || ',' || l_description;
1253         END IF;
1254 
1255       END LOOP;
1256 
1257       RETURN l_token_desc;
1258 
1259     EXCEPTION
1260       WHEN OTHERS THEN
1261         -- supressing the exception since this function is
1262         -- called within an exception
1263         l_token_desc := 'Error';
1264         RETURN l_token_desc;
1265     END get_aus_desc;
1266 
1267 
1268     PROCEDURE drop_ss_unit_attempt    (
1269                                             p_person_id IN NUMBER,
1270                                             p_course_cd IN VARCHAR2,
1271                                             p_course_version IN NUMBER ,
1272                                             p_uoo_id IN NUMBER,
1273                                             p_load_cal_type IN VARCHAR2,
1274                                             p_load_sequence_number IN NUMBER,
1275                                             p_dcnt_reason_cd IN VARCHAR2 ,
1276                                             p_admin_unit_status IN VARCHAR2 ,
1277                                             p_effective_date IN DATE ,
1278                                             p_dropped_uooids OUT NOCOPY VARCHAR2,
1279                                             p_return_status OUT NOCOPY VARCHAR2,
1280                                             p_message OUT NOCOPY VARCHAR2,
1281                                             p_ss_session_id IN NUMBER) AS
1282 
1283   -------------------------------------------------------------------------------------------
1284   -- Created by  : Basanth Kumar D, Oracle Student Systems Oracle IDC
1285   -- Purpose : This procedure is called from drop page to drop the unit selected by  the user
1286   -- Along with user selected unit other units which fail validtion in deny mode of that setup
1287   -- are also dropped
1288   --Change History:
1289   --Who         When            What
1293 
1290   --amuthu      9-Aug-2006      If the default drop reason cannot be determined then
1291   --                            stopping the further processing and showing a newly added message
1292   -------------------------------------------------------------------------------------------
1294 
1295 
1296     l_enr_meth_type             igs_en_method_type.enr_method_type%TYPE;
1297 
1298     l_alternate_code            igs_ca_inst.alternate_code%TYPE;
1299     l_acad_cal_type             igs_ca_inst.cal_type%TYPE;
1300     l_acad_ci_sequence_number   igs_ca_inst.sequence_number%TYPE;
1301     l_acad_start_dt             DATE;
1302     l_acad_end_dt               DATE;
1303 
1304     l_enr_cat                   igs_ps_type.enrolment_cat%TYPE;
1305     l_enr_cal_type              IGS_CA_INST.cal_type%TYPE;
1306     l_enr_ci_seq                IGS_CA_INST.sequence_number%TYPE;
1307     l_enr_categories            VARCHAR2(255);
1308     l_enr_comm                  VARCHAR2(1000);
1309 
1310     l_deny_warn_min_cp          VARCHAR2(10);
1311     l_deny_warn_att_type        VARCHAR2(30);
1312     l_deny_warn_coreq           VARCHAR2(10);
1313     l_deny_warn_prereq          VARCHAR2(10);
1314     -- bmerugu added for core drop validation
1315     l_deny_warn_core		VARCHAR2(10);
1316     l_person_type               igs_pe_typ_instances.person_type_code%TYPE;
1317 
1318     l_message                   VARCHAR2(100);
1319     l_return_status             VARCHAR2(5);
1320 
1321     l_drop_uoo_ids              VARCHAR2(1000);
1322     l_temp_failed_uooids        VARCHAR2(1000);
1323     l_uooids_dropped            VARCHAR2(1000);
1324 
1325     l_enc_message_name          VARCHAR2(2000);
1326     l_app_short_name            VARCHAR2(100);
1327     l_msg_index                 NUMBER;
1328     l_message_name              VARCHAR2(4000);
1329     l_token                     VARCHAR2(2000);
1330 
1331 
1332     CURSOR c_dcnt_rsn IS
1333     SELECT discontinuation_reason_cd
1334     FROM igs_en_dcnt_reasoncd
1335     WHERE  NVL(closed_ind,'N') ='N'
1336     AND  dflt_ind ='Y'
1337     AND dcnt_unit_ind ='Y'
1338     AND s_discontinuation_reason_type IS NULL;
1339 
1340     l_dcnt_reason_cd          igs_en_dcnt_reasoncd.discontinuation_reason_cd%TYPE;
1341 
1342     -- Cursor to get the coo_id of the student.
1343     CURSOR cur_coo_id IS
1344     SELECT coo_id coo_id
1345     FROM   igs_en_stdnt_ps_att
1346     WHERE  person_id = p_person_id
1347     AND    course_cd = p_course_cd ;
1348 
1349     l_attendance_type_reach   BOOLEAN;
1350     l_cur_coo_id              cur_coo_id%ROWTYPE;
1351     l_attendance_types        VARCHAR2(100);
1352     resource_busy  EXCEPTION;
1353     NO_AUSL_RECORD_FOUND EXCEPTION;
1354     PRAGMA EXCEPTION_INIT(NO_AUSL_RECORD_FOUND , -20010);
1355     PRAGMA EXCEPTION_INIT(resource_busy,-00054);
1356 
1357     BEGIN
1358 
1359     igs_en_add_units_api.g_ss_session_id := p_ss_session_id;
1360 
1361     igs_en_add_units_api.delete_ss_warnings
1362                             (
1363                               p_person_id             => p_person_id,
1364                               p_course_cd             => p_course_cd,
1365                               p_load_cal_type         => p_load_cal_type,
1366                               p_load_sequence_number  => p_load_sequence_number,
1367                               p_uoo_id                => p_uoo_id,
1368                               p_message_for           => NULL,
1369                               p_delete_steps          => 'DROP'
1370                               );
1371 
1372       -- smaddali added this cursor to lock the row , bug#4864437
1373       OPEN C_SUA_lock (p_person_id,p_course_cd,p_uoo_id);
1374       FETCH C_SUA_lock INTO l_lock_rec;
1375       CLOSE C_SUA_lock;
1376 
1377       IF l_lock_rec.unit_attempt_status IN ('DROPPED','DISCONTIN') THEN
1378           p_message := 'IGS_GE_RECORD_CHANGED';
1379           p_return_status := 'E';
1380           igs_en_add_units_api.g_ss_session_id := NULL;
1381           RETURN;
1382       END IF;
1383 
1384     igs_en_gen_017.enrp_get_enr_method(
1385                              p_enr_method_type => l_enr_meth_type,
1386                              p_error_message   => l_message,
1387                              p_ret_status      => l_return_status
1388                              );
1389      IF l_return_status = 'FALSE' OR l_message IS NOT NULL THEN
1390 
1391       p_message := l_message;
1392       p_return_status := 'E';
1393       igs_en_add_units_api.g_ss_session_id := NULL;
1394       RETURN;
1395 
1396      END IF ;
1397 
1398 
1399     IF p_dcnt_reason_cd IS NULL THEN
1400 
1401       OPEN c_dcnt_rsn;
1402       FETCH c_dcnt_rsn INTO l_dcnt_reason_cd;
1403       CLOSE c_dcnt_rsn;
1404 
1405       IF l_dcnt_reason_cd IS NULL THEN
1406         p_message := 'IGS_EN_DFLT_DCNT_RSN_NOT_SETUP';
1407         p_return_status := 'E';
1408         igs_en_add_units_api.g_ss_session_id := NULL;
1409         RETURN;
1410       END IF;
1411 
1412     ELSE
1413 
1414       l_dcnt_reason_cd := p_dcnt_reason_cd;
1415 
1416     END IF;
1417 
1418     l_alternate_code := Igs_En_Gen_002.Enrp_Get_Acad_Alt_Cd(
1419                         p_cal_type                => p_load_cal_type,
1420                         p_ci_sequence_number      => p_load_sequence_number,
1421                         p_acad_cal_type           => l_acad_cal_type,
1422                         p_acad_ci_sequence_number => l_acad_ci_sequence_number,
1423                         p_acad_ci_start_dt        => l_acad_start_dt,
1424                         p_acad_ci_end_dt          => l_acad_end_dt,
1425                         p_message_name            => l_message );
1426 
1427     IF l_message IS NOT NULL THEN
1428 
1429       p_message := l_message;
1433 
1430       p_return_status := 'E';
1431       igs_en_add_units_api.g_ss_session_id := NULL;
1432       RETURN;
1434     END IF;
1435 
1436 
1437 
1438     l_enr_cat := igs_en_gen_003.enrp_get_enr_cat(
1439                         p_person_id                 =>  p_person_id,
1440                         p_course_cd                 =>  p_course_cd ,
1441                         p_cal_type                  =>  l_acad_cal_type ,
1442                         p_ci_sequence_number        =>  l_acad_ci_sequence_number,
1443                         p_session_enrolment_cat     =>  NULL,
1444                         p_enrol_cal_type            =>  l_enr_cal_type,
1445                         p_enrol_ci_sequence_number  =>  l_enr_ci_seq,
1446                         p_commencement_type         =>  l_enr_comm,
1447                         p_enr_categories            =>  l_enr_categories
1448                         );
1449 
1450 
1451     IF l_enr_comm = 'BOTH' THEN
1452 
1453      l_enr_comm :='ALL';
1454 
1455     END IF;
1456 
1457     l_message:= NULL;
1458 
1459     l_person_type := igs_en_gen_008.enrp_get_person_type(p_course_cd);
1460 
1461     l_deny_warn_min_cp  := igs_ss_enr_details.get_notification(
1462                                 p_person_type            => l_person_type,
1463                                 p_enrollment_category    => l_enr_cat,
1464                                 p_comm_type              => l_enr_comm,
1465                                 p_enr_method_type        => l_enr_meth_type,
1466                                 p_step_group_type        => 'PROGRAM',
1467                                 p_step_type              => 'FMIN_CRDT',
1468                                 p_person_id              => p_person_id,
1469                                 p_message                => l_message
1470                                 ) ;
1471 
1472 
1473     IF l_message IS NOT NULL THEN
1474 
1475           p_message := l_message;
1476           p_return_status := 'E';
1477           igs_en_add_units_api.g_ss_session_id := NULL;
1478           RETURN;
1479 
1480     END IF;
1481 
1482 
1483     l_deny_warn_att_type  := igs_ss_enr_details.get_notification(
1484                                         p_person_type            => l_person_type,
1485                                         p_enrollment_category    => l_enr_cat,
1486                                         p_comm_type              => l_enr_comm,
1487                                         p_enr_method_type        => l_enr_meth_type,
1488                                         p_step_group_type        => 'PROGRAM',
1489                                         p_step_type              => 'FATD_TYPE',
1490                                         p_person_id              => p_person_id,
1491                                         p_message                => l_message
1492                                         ) ;
1493     IF l_message IS NOT NULL THEN
1494 
1495           p_message := l_message;
1496           p_return_status := 'E';
1497           igs_en_add_units_api.g_ss_session_id := NULL;
1498           RETURN;
1499 
1500     END IF;
1501 
1502     --bmerugu added
1503     -- Get the value of Deny/Warn Flag for unit step 'DROP_CORE'
1504     l_deny_warn_core := igs_ss_enr_details.get_notification(
1505 				p_person_type            => l_person_type,
1506 				p_enrollment_category    => l_enr_cat,
1507 				p_comm_type              => l_enr_comm,
1508 				p_enr_method_type        => l_enr_meth_type,
1509 				p_step_group_type        => 'UNIT',
1510 				p_step_type              => 'DROP_CORE',
1511 				p_person_id              => p_person_id,
1512 				p_message                => l_message
1513 				) ;
1514 
1515     IF l_message IS NOT NULL THEN
1516           p_message := l_message;
1517           p_return_status := 'E';
1518           igs_en_add_units_api.g_ss_session_id := NULL;
1519           RETURN;
1520     END IF;
1521 
1522     IF l_deny_warn_att_type  IS NOT NULL THEN
1523 
1524       OPEN  cur_coo_id;
1525       FETCH cur_coo_id INTO l_cur_coo_id;
1526       CLOSE cur_coo_id;
1527 
1528       l_attendance_type_reach := TRUE;
1529 
1530       -- Check if the Forced Attendance Type has already been reached for the Student
1531       l_attendance_type_reach := igs_en_val_sca.enrp_val_coo_att(
1532                                             p_person_id          => p_person_id,
1533                                             p_coo_id             => l_cur_coo_id.coo_id,
1534                                             p_cal_type           => l_acad_cal_type,
1535                                             p_ci_sequence_number => l_acad_ci_sequence_number,
1536                                             p_message_name       => l_message,
1537                                             p_attendance_types   => l_attendance_types,
1538                                             p_load_or_teach_cal_type => p_load_cal_type,
1539                                             p_load_or_teach_seq_number => p_load_sequence_number
1540                                             );
1541 
1542       -- Assign values to the parameter p_deny_warn_att based on if Attendance Type has not been already reached or not.
1543       IF l_attendance_type_reach THEN
1544           l_deny_warn_att_type  := 'AttTypReached' ;
1545       ELSE
1546           l_deny_warn_att_type  := 'AttTypNotReached' ;
1547       END IF ;
1548 
1549     END IF ;
1550 
1551     l_message := NULL;
1552 
1553     l_deny_warn_coreq  := igs_ss_enr_details.get_notification(
1554                                 p_person_type            => l_person_type,
1555                                 p_enrollment_category    => l_enr_cat,
1556                                 p_comm_type              => l_enr_comm,
1557                                 p_enr_method_type        => l_enr_meth_type,
1561                                 p_message                => l_message
1558                                 p_step_group_type        => 'UNIT',
1559                                 p_step_type              => 'COREQ',
1560                                 p_person_id              => p_person_id,
1562                                 ) ;
1563     IF l_message IS NOT NULL THEN
1564 
1565           p_message := l_message;
1566           p_return_status := 'E';
1567           igs_en_add_units_api.g_ss_session_id := NULL;
1568           RETURN;
1569 
1570     END IF;
1571 
1572     l_message := NULL;
1573     l_deny_warn_prereq := igs_ss_enr_details.get_notification(
1574                                 p_person_type            => l_person_type,
1575                                 p_enrollment_category    => l_enr_cat,
1576                                 p_comm_type              => l_enr_comm,
1577                                 p_enr_method_type        => l_enr_meth_type,
1578                                 p_step_group_type        => 'UNIT',
1579                                 p_step_type              => 'PREREQ',
1580                                 p_person_id              => p_person_id,
1581                                 p_message                => l_message
1582                                 ) ;
1583     IF l_message IS NOT NULL THEN
1584 
1585           p_message := l_message;
1586           p_return_status := 'E';
1587           igs_en_add_units_api.g_ss_session_id := NULL;
1588           RETURN;
1589 
1590     END IF;
1591 
1592     l_drop_uoo_ids := p_uoo_id;
1593     l_uooids_dropped := NULL;
1594     l_return_status := NULL;
1595     p_message := NULL;
1596 
1597      -- smaddali 8-dec-2005   added this global variable to bypass update spa,
1598      -- matriculation  and reserved seat counts for DROP  : bug#4864437
1599     igs_en_su_attempt_pkg.pkg_source_of_drop := 'DROP';
1600 
1601 
1602     --  This  loop drop the units passed and in that process collects
1603     -- all the uooids that are failing (prereq/coreq in deny mode) because of dropping
1604     -- the passed units and these units are passed in the next iteration to be dropped .
1605     -- This process is repeated untill no units fail validations
1606     LOOP
1607 
1608       drop_student_unit_attempts(
1609                         p_person_id,
1610                         p_course_cd,
1611                         p_course_version,
1612                         p_uoo_id, -- uoo_id passed to api from page
1613                         l_drop_uoo_ids,
1614                         l_acad_cal_type,
1615                         l_acad_ci_sequence_number,
1616                         p_load_cal_type,
1617                         p_load_sequence_number,
1618                         l_enr_cat,
1619                         l_enr_comm,
1620                         l_enr_meth_type,
1621                         l_dcnt_reason_cd,
1622                         p_admin_unit_status,
1623                         p_effective_date,
1624                         l_deny_warn_coreq,
1625                         l_deny_warn_prereq,
1626                         l_deny_warn_min_cp,
1627                         l_deny_warn_att_type,
1628 			            l_deny_warn_core,
1629                         l_temp_failed_uooids,  -- uooids failed in this loop
1630                         l_uooids_dropped,    --- uooids dropped in this loop
1631                         p_message,
1632                         l_return_status);
1633 
1634       IF l_return_status = 'E' AND p_message IS NOT NULL THEN
1635         igs_en_su_attempt_pkg.pkg_source_of_drop := NULL;
1636         p_return_status := 'E';
1637         igs_en_add_units_api.g_ss_session_id := NULL;
1638         RETURN;
1639       END IF;
1640 
1641       IF p_dropped_uooids IS NULL THEN
1642         p_dropped_uooids := l_uooids_dropped;
1643       ELSE
1644         p_dropped_uooids := p_dropped_uooids||','||l_uooids_dropped;
1645       END IF;
1646 
1647       EXIT WHEN  l_temp_failed_uooids IS NULL OR l_return_status = 'E' ;
1648 
1649       l_drop_uoo_ids := l_temp_failed_uooids;
1650       l_temp_failed_uooids := NULL;
1651       l_return_status := NULL;
1652       l_uooids_dropped := NULL;
1653 
1654     END LOOP;
1655     igs_en_su_attempt_pkg.pkg_source_of_drop := NULL;
1656     igs_en_add_units_api.g_ss_session_id := NULL;
1657 
1658   EXCEPTION
1659     WHEN NO_AUSL_RECORD_FOUND THEN
1660       igs_en_su_attempt_pkg.pkg_source_of_drop := NULL;
1661       igs_en_add_units_api.g_ss_session_id := NULL;
1662       p_message := 'IGS_SS_CANTDET_ADM_UNT_STATUS';
1663       p_return_status := 'E';
1664       RETURN;
1665 
1666     WHEN resource_busy THEN
1667       igs_en_su_attempt_pkg.pkg_source_of_drop := NULL;
1668       igs_en_add_units_api.g_ss_session_id := NULL;
1669       p_message := 'IGS_GE_RECORD_LOCKED';
1670       p_return_status := 'E';
1671       RETURN;
1672 
1673     WHEN APP_EXCEPTION.APPLICATION_EXCEPTION THEN
1674        igs_en_su_attempt_pkg.pkg_source_of_drop := NULL;
1675        igs_en_add_units_api.g_ss_session_id := NULL;
1676         IGS_GE_MSG_STACK.GET(-1, 'T', l_enc_message_name, l_msg_index);
1677         FND_MESSAGE.PARSE_ENCODED(l_enc_message_name,l_app_short_name,l_message_name);
1678         l_token := FND_MESSAGE.GET_TOKEN('LIST',NULL);
1679         IF l_token IS NOT NULL THEN
1680          l_message_name := l_message_name || '*' || get_aus_desc(l_token);
1681         END IF;
1682         p_return_status := 'E';
1683         p_message := l_message_name;
1684         RETURN;
1685 
1686     WHEN OTHERS THEN
1687         igs_en_su_attempt_pkg.pkg_source_of_drop := NULL;
1688         igs_en_add_units_api.g_ss_session_id := NULL;
1689         Fnd_Message.Set_Name('IGS','IGS_GE_UNHANDLED_EXP');
1690         FND_MESSAGE.SET_TOKEN('NAME', 'IGS_EN_DROP_UNITS_API.drop_ss_unit_attempt');
1694         END IF;
1691         IGS_GE_MSG_STACK.ADD;
1692         IF (FND_LOG.LEVEL_UNEXPECTED >= g_debug_level ) THEN
1693               FND_LOG.STRING(fnd_log.level_unexpected, 'igs.patch.115.sql.igs_en_drop_units_api.drop_ss_unit_attempt :',SQLERRM);
1695         ROLLBACK;
1696         RAISE;
1697 
1698   END drop_ss_unit_attempt;
1699 
1700 
1701   FUNCTION update_dropped_units (
1702             p_person_id igs_en_su_attempt.person_id%TYPE,
1703             p_course_cd igs_en_su_attempt.course_cd%TYPE,
1704             p_uoo_ids VARCHAR2,
1705             p_discontinuation_reason_cd VARCHAR2 )
1706             RETURN VARCHAR2 AS
1707   BEGIN
1708 
1709     RETURN update_dropped_units(p_person_id, p_course_cd, p_uoo_ids, p_discontinuation_reason_cd, NULL  );
1710 
1711   END update_dropped_units;
1712 
1713   FUNCTION update_dropped_units (
1714             p_person_id igs_en_su_attempt.person_id%TYPE,
1715             p_course_cd igs_en_su_attempt.course_cd%TYPE,
1716             p_uoo_ids VARCHAR2,
1717             p_discontinuation_reason_cd VARCHAR2,
1718             p_admin_unit_status VARCHAR2)
1719             RETURN VARCHAR2 AS
1720 
1721     l_discont_reason_cd   igs_en_dcnt_reasoncd.discontinuation_reason_cd%TYPE;
1722 
1723     TYPE c_ref_cursor IS REF CURSOR;
1724     c_upd_units           c_ref_cursor;
1725 
1726     upd_units_rec         igs_en_su_attempt%ROWTYPE;
1727     l_admin_unit_status   igs_en_su_attempt.administrative_unit_status%TYPE;
1728   BEGIN
1729 --check that the uoo_ids list to be modified is not null
1730 
1731 IF p_uoo_ids IS NULL THEN
1732 FND_MESSAGE.set_name('IGS', 'IGS_GE_RECORD_CHANGED');
1733  IGS_GE_MSG_STACK.ADD;
1734 APP_EXCEPTION.RAISE_EXCEPTION;
1735 END IF;
1736 
1737   --modified sqlquery for bug 5037726,sql id : 14792801
1738     OPEN c_upd_units FOR
1739                           'SELECT sua.* FROM igs_En_su_attempt sua
1740                            WHERE person_id = :1
1741                            AND course_cd = :2
1742                            AND uoo_id IN ('||p_uoo_ids||')' USING p_person_id,p_course_cd ;
1743 
1744     LOOP
1745 
1746       FETCH c_upd_units INTO upd_units_rec;
1747 
1748       EXIT WHEN  c_upd_units%NOTFOUND;
1749 
1750       IF p_admin_unit_status IS NULL THEN
1751         l_admin_unit_status := upd_units_rec.administrative_unit_status;
1752       ELSE
1753         l_admin_unit_status := p_admin_unit_status;
1754       END IF;
1755 
1756       -- Call update_row of the student unit attempt table handler i.e
1757       igs_En_su_Attempt_pkg.update_row( X_ROWID                        =>     upd_units_rec.row_id                        ,
1758                                         X_PERSON_ID                    =>     upd_units_rec.person_id                      ,
1759                                         X_COURSE_CD                    =>     upd_units_rec.course_cd                      ,
1760                                         X_UNIT_CD                      =>     upd_units_rec.unit_cd                        ,
1761                                         X_CAL_TYPE                     =>     upd_units_rec.cal_type                       ,
1762                                         X_CI_SEQUENCE_NUMBER           =>     upd_units_rec.ci_sequence_number             ,
1763                                         X_VERSION_NUMBER               =>     upd_units_rec.version_number                 ,
1764                                         X_LOCATION_CD                  =>     upd_units_rec.location_cd                    ,
1765                                         X_UNIT_CLASS                   =>     upd_units_rec.unit_class                     ,
1766                                         X_CI_START_DT                  =>     upd_units_rec.ci_start_dt                    ,
1767                                         X_CI_END_DT                    =>     upd_units_rec.ci_end_dt                      ,
1768                                         X_UOO_ID                       =>     upd_units_rec.uoo_id                         ,
1769                                         X_ENROLLED_DT                  =>     upd_units_rec.enrolled_dt                    ,
1770                                         X_UNIT_ATTEMPT_STATUS          =>     upd_units_rec.unit_attempt_status            ,
1771                                         X_ADMINISTRATIVE_UNIT_STATUS   =>     l_admin_unit_status                          ,
1772                                         X_DISCONTINUED_DT              =>     upd_units_rec.discontinued_dt                ,
1773                                         X_RULE_WAIVED_DT               =>     upd_units_rec.rule_waived_dt                 ,
1774                                         X_RULE_WAIVED_PERSON_ID        =>     upd_units_rec.rule_waived_person_id          ,
1775                                         X_NO_ASSESSMENT_IND            =>     upd_units_rec.no_assessment_ind              ,
1776                                         X_SUP_UNIT_CD                  =>     upd_units_rec.sup_unit_cd                    ,
1777                                         X_SUP_VERSION_NUMBER           =>     upd_units_rec.sup_version_number             ,
1778                                         X_EXAM_LOCATION_CD             =>     upd_units_rec.exam_location_cd               ,
1779                                         X_ALTERNATIVE_TITLE            =>     upd_units_rec.alternative_title              ,
1780                                         X_OVERRIDE_ENROLLED_CP         =>     upd_units_rec.override_enrolled_cp           ,
1781                                         X_OVERRIDE_EFTSU               =>     upd_units_rec.override_eftsu                 ,
1782                                         X_OVERRIDE_ACHIEVABLE_CP       =>     upd_units_rec.override_achievable_cp         ,
1783                                         X_OVERRIDE_OUTCOME_DUE_DT      =>     upd_units_rec.override_outcome_due_dt        ,
1784                                         X_OVERRIDE_CREDIT_REASON       =>     upd_units_rec.override_credit_reason         ,
1785                                         X_ADMINISTRATIVE_PRIORITY      =>     upd_units_rec.administrative_priority        ,
1786                                         X_WAITLIST_DT                  =>     upd_units_rec.waitlist_dt                    ,
1787                                         X_DCNT_REASON_CD               =>     p_discontinuation_reason_cd                  , --- upodate with passed discont reason cd
1788                                         X_MODE                         =>     'R'                                          ,
1789                                         X_GS_VERSION_NUMBER            =>     upd_units_rec.gs_version_number              ,
1790                                         X_ENR_METHOD_TYPE              =>     upd_units_rec.enr_method_type                ,
1791                                         X_FAILED_UNIT_RULE             =>     upd_units_rec.failed_unit_rule               ,
1792                                         X_CART                         =>     upd_units_rec.cart                           ,
1793                                         X_RSV_SEAT_EXT_ID              =>     upd_units_rec.rsv_seat_ext_id                ,
1794                                         X_ORG_UNIT_CD                  =>     upd_units_rec.org_unit_cd                    ,
1795                                         X_SESSION_ID                   =>     upd_units_rec.session_id                     ,
1796                                         X_GRADING_SCHEMA_CODE          =>     upd_units_rec.grading_schema_code            ,
1797                                         X_DEG_AUD_DETAIL_ID            =>     upd_units_rec.deg_aud_detail_id              ,
1798                                         X_STUDENT_CAREER_TRANSCRIPT    =>     upd_units_rec.student_career_transcript,
1799                                         X_STUDENT_CAREER_STATISTICS    =>      upd_units_rec.student_career_statistics,
1800                                         X_ATTRIBUTE_CATEGORY           =>      upd_units_rec.attribute_category,
1801                                         X_ATTRIBUTE1                   =>      upd_units_rec.attribute1,
1802                                         X_ATTRIBUTE2                   =>      upd_units_rec.attribute2,
1803                                         X_ATTRIBUTE3                   =>      upd_units_rec.attribute3,
1804                                         X_ATTRIBUTE4                   =>      upd_units_rec.attribute4,
1805                                         X_ATTRIBUTE5                   =>      upd_units_rec.attribute5,
1806                                         X_ATTRIBUTE6                   =>      upd_units_rec.attribute6,
1807                                         X_ATTRIBUTE7                   =>      upd_units_rec.attribute7,
1808                                         X_ATTRIBUTE8                   =>      upd_units_rec.attribute8,
1809                                         X_ATTRIBUTE9                   =>      upd_units_rec.attribute9,
1810                                         X_ATTRIBUTE10                  =>      upd_units_rec.attribute10,
1811                                         X_ATTRIBUTE11                  =>      upd_units_rec.attribute11,
1812                                         X_ATTRIBUTE12                  =>      upd_units_rec.attribute12,
1813                                         X_ATTRIBUTE13                  =>      upd_units_rec.attribute13,
1814                                         X_ATTRIBUTE14                  =>      upd_units_rec.attribute14,
1815                                         X_ATTRIBUTE15                  =>      upd_units_rec.attribute15,
1816                                         X_ATTRIBUTE16                  =>      upd_units_rec.attribute16,
1817                                         X_ATTRIBUTE17                  =>      upd_units_rec.attribute17,
1818                                         X_ATTRIBUTE18                  =>      upd_units_rec.attribute18,
1819                                         X_ATTRIBUTE19                  =>      upd_units_rec.attribute19,
1820                                         X_ATTRIBUTE20                  =>      upd_units_rec.attribute20,
1821                                         X_WAITLIST_MANUAL_IND          =>      upd_units_rec.waitlist_manual_ind ,
1822                                         X_WLST_PRIORITY_WEIGHT_NUM     =>      upd_units_rec.wlst_priority_weight_num,
1823                                         X_WLST_PREFERENCE_WEIGHT_NUM   =>      upd_units_rec.wlst_preference_weight_num,
1824                                         X_CORE_INDICATOR_CODE          =>      upd_units_rec.core_indicator_code
1825                                       );
1826 
1827     END LOOP;
1828     RETURN 'TRUE' ;
1829 
1830   EXCEPTION
1831      WHEN APP_EXCEPTION.APPLICATION_EXCEPTION THEN
1832         ROLLBACK;
1833         RAISE;
1834     WHEN OTHERS THEN
1835 
1836         Fnd_Message.Set_Name('IGS','IGS_GE_UNHANDLED_EXP');
1837         FND_MESSAGE.SET_TOKEN('NAME', 'IGS_EN_DROP_UNITS_API.update_dropped_units');
1838         IGS_GE_MSG_STACK.ADD;
1839         IF (FND_LOG.LEVEL_UNEXPECTED >= g_debug_level ) THEN
1840               FND_LOG.STRING(fnd_log.level_unexpected, 'igs.patch.115.sql.igs_en_drop_units_api.update_dropped_units:',SQLERRM);
1841         END IF;
1842         ROLLBACK;
1843         RAISE;
1844 
1845   END update_dropped_units;
1846 
1847 END igs_en_drop_units_api;