DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGS_HE_IDENTIFY_TARGET_POP

Source


1 PACKAGE BODY igs_he_identify_target_pop AS
2 /* $Header: IGSHE25B.pls 120.4 2006/09/12 01:18:21 jtmathew ship $ */
3 
4 PROCEDURE dlhe_identify_population (errbuf            OUT NOCOPY     VARCHAR2,
5                                     retcode           OUT NOCOPY     NUMBER,
6                                     p_submission_name IN  igs_he_sub_rtn_qual.submission_name%TYPE,
7                                     p_return_name     IN  igs_he_sub_rtn_qual.return_name%TYPE,
8                                     p_qual_period     IN  igs_he_sub_rtn_qual.qual_period_code%TYPE
9                                   ) IS
10  /******************************************************************
11   Created By      : prasad marada
12   Date Created By : 20-Apr-2003
13   Purpose         : In this procedure identify the all qualifying periods
14                     and call the identify spa procedure
15   Known limitations,enhancements,remarks:
16   Change History
17   Who       When         What
18   anwest    18-JAN-2006  Bug# 4950285 R12 Disable OSS Mandate
19  *******************************************************************/
20 
21      -- Get the all qualifying periods under the submission order by closed
22      CURSOR cur_qual_period (cp_submission_name igs_he_sub_rtn_qual.submission_name%TYPE,
23                              cp_return_name     igs_he_sub_rtn_qual.return_name%TYPE,
24                              cp_qual_period     igs_he_sub_rtn_qual.qual_period_code%TYPE) IS
25      SELECT qual.qual_period_code,
26             qual.qual_period_desc,
27             qual.qual_period_type,
28             qual.qual_period_start_date,
29             qual.qual_period_end_date,
30             qual.closed_ind
31      FROM igs_he_sub_rtn_qual qual,
32           igs_he_usr_rtn_clas urc
33      WHERE qual.submission_name  = cp_submission_name
34        AND qual.return_name      = cp_return_name
35        AND qual.qual_period_code = NVL(cp_qual_period, qual.qual_period_code)
36        AND qual.qual_period_type IN ('L','R')
37        AND qual.user_return_subclass = urc.user_return_subclass
38        AND urc.system_return_class_type = 'DLHE'
39        ORDER BY qual.closed_ind ASC;
40 
41  BEGIN
42 
43          --anwest 18-JAN-2006 Bug# 4950285 R12 Disable OSS Mandate
44          IGS_GE_GEN_003.SET_ORG_ID;
45 
46          retcode := 0;
47          -- Check if UCAS and HESA are enabled, ie country = UK
48         IF NOT Igs_Uc_Utils.is_ucas_hesa_enabled  THEN
49           fnd_message.set_name('IGS','IGS_UC_HE_NOT_ENABLED');
50           fnd_file.put_line(fnd_file.log, fnd_message.get);
51           errbuf  := fnd_message.get ;
52           retcode := 2;
53           RETURN;
54         END IF;
55 
56 
57         -- Get the all qualifying periods under the submission and call the identify spa process for each qual period
58          FOR cur_qual_period_rec IN cur_qual_period (p_submission_name,
59                                                      p_return_name,
60                                                      p_qual_period) LOOP
61 
62               -- Report the Qualifying period details in the log file
63              fnd_message.set_name('IGS','IGS_HE_DLHE_QUAL_PERIOD');
64              fnd_message.set_token('QUAL_PERIOD',cur_qual_period_rec.qual_period_code);
65              fnd_message.set_token('DESC',cur_qual_period_rec.qual_period_desc);
66              fnd_message.set_token('TYPE',cur_qual_period_rec.qual_period_type);
67              fnd_file.put_line(fnd_file.log,fnd_message.get);
68               -- Call the dlhe_identify_spa procedure for each qualifying period
69              igs_he_identify_target_pop.Dlhe_identify_spa(p_submission_name => p_submission_name,
70                                                     p_return_name     => p_return_name,
71                                                     p_qual_period     => cur_qual_period_rec.qual_period_code,
72                                                     p_qual_type       => cur_qual_period_rec.qual_period_type,
73                                                     p_qual_start_date => cur_qual_period_rec.qual_period_start_date,
74                                                     p_qual_end_date   => cur_qual_period_rec.qual_period_end_date,
75                                                     p_closed_ind      => cur_qual_period_rec.closed_ind
76                                                    );
77          END LOOP;
78 
79     EXCEPTION
80      WHEN OTHERS THEN
81          ROLLBACK;
82          Fnd_Message.Set_Name('IGS','IGS_GE_UNHANDLED_EXP');
83          Fnd_Message.Set_Token('NAME','igs_he_identify_target_pop.dlhe_identify_population');
84          fnd_file.put_line(fnd_file.log, fnd_message.get);
85          errbuf  := fnd_message.get ;
86          retcode := 2;
87 
88          IGS_GE_MSG_STACK.CONC_EXCEPTION_HNDL;
89 
90  END dlhe_identify_population;
91 
92  PROCEDURE dlhe_identify_spa (p_submission_name IN  igs_he_sub_rtn_qual.submission_name%TYPE,
93                               p_return_name     IN  igs_he_sub_rtn_qual.return_name%TYPE,
94                               p_qual_period     IN  igs_he_sub_rtn_qual.qual_period_code%TYPE,
95                               p_qual_type       IN  igs_he_sub_rtn_qual.qual_period_type%TYPE,
96                               p_qual_start_date IN  igs_he_sub_rtn_qual.qual_period_start_date%TYPE,
97                               p_qual_end_date   IN  igs_he_sub_rtn_qual.qual_period_end_date%TYPE,
98                               p_closed_ind      IN  igs_he_sub_rtn_qual.closed_ind%TYPE
99                             ) IS
100 
101  /******************************************************************
102   Created By      :  prasad marada
103   Date Created By :  20-Apr-2003
104   Purpose         :  Identify the Leavers/Research students and call the Process_spa
105                      Prcoedure for each student.
106   Known limitations,enhancements,remarks:
107   Change History
108   Who       When         What
109   smaddali 07-Jan-04  Modified cursor cur_leavers_std to remove the condition
110                       sca.course_attempt_status IN ('COMPLETED','DISCONTIN'), for bug#3335847
111   jbaber   29-Jan-06  Modified cur_leavers_std and cur_research_std to exclude flagged
112                       Program and POOUS records for HE305 - Extract Improvements
113  *******************************************************************/
114 
115       -- Get the dlhe rowid for closed qualifying period records
116      CURSOR cur_closed_dlhe (cp_submission_name igs_he_sub_rtn_qual.submission_name%TYPE,
117                              cp_return_name     igs_he_sub_rtn_qual.return_name%TYPE,
118                              cp_qual_period     igs_he_sub_rtn_qual.qual_period_code%TYPE) IS
119      SELECT rowid
120      FROM igs_he_stdnt_dlhe
121      WHERE submission_name  = cp_submission_name
122      AND return_name        = cp_return_name
123      AND qual_period_code   = cp_qual_period
124      AND dlhe_record_status = 'NST';
125 
126     -- Get the LEAVERS Students person_id and SPA details
127     -- smaddali modified cursor to remove condition course_attempt_status IN 'COMPLETED','DISCONTIN',
128     -- because the status need not be only completed/discontinued for a leaver, bug 3335847
129      CURSOR cur_leavers_std (cp_qual_start_dt igs_he_sub_rtn_qual.qual_period_start_date%TYPE,
130                              cp_qual_end_dt igs_he_sub_rtn_qual.qual_period_end_date%TYPE) IS
131      SELECT hst.person_id,
132             hst.course_cd,
133             sca.version_number
134      FROM  igs_en_stdnt_ps_att  sca,
135            igs_he_st_spa   hst,
136            igs_he_st_prog_all  hpg
137      WHERE sca.person_id  = hst.person_id
138       AND  sca.course_cd  = hst.course_cd
139       AND  sca.course_cd  = hpg.course_cd
140       AND  sca.version_number = hpg.version_number
141       AND  NVL(hpg.exclude_flag, 'N') = 'N'
142       AND  NVL(hst.exclude_flag, 'N') = 'N'
143       AND  ((sca.discontinued_dt BETWEEN cp_qual_start_dt AND cp_qual_end_dt)
144              OR  (sca.course_rqrmnts_complete_dt BETWEEN cp_qual_start_dt AND cp_qual_end_dt))
145       ORDER BY hst.person_id;
146 
147        l_leavers_std  cur_leavers_std%ROWTYPE;
148 
149        -- Get the RESEARCH students person_id and their SPAs
150        CURSOR cur_research_std  IS
151        SELECT hst.person_id,
152               hst.course_cd,
153               sca.version_number,
154               hst.student_inst_number,
155               hst.commencement_dt  hst_commencement_dt,
156               sca.commencement_dt  sca_commencement_dt
157        FROM   igs_en_stdnt_ps_att sca,
158               igs_he_st_spa hst,
159               igs_he_st_prog_all  hpg,
160               igs_ps_ver    pv,
161               igs_ps_type   pt
162        WHERE hst.person_id = sca.person_id
163          AND hst.course_cd = sca.course_cd
164          AND sca.course_cd      = hpg.course_cd
165          AND sca.version_number = hpg.version_number
166          AND sca.course_cd      = pv.course_cd
167          AND sca.version_number = pv.version_number
168          AND pt.course_type     = pv.course_type
169          AND pt.research_type_ind = 'Y'
170          AND NVL(hpg.exclude_flag, 'N') = 'N'
171          AND NVL(hst.exclude_flag, 'N') = 'N'
172          ORDER BY hst.person_id;
173 
174          l_research_std cur_research_std%ROWTYPE;
175 
176          l_comdate igs_he_ex_rn_dat_fd.value%TYPE;
177          l_previous_person_id igs_pe_person_base_v.person_id%TYPE;
178 
179          -- Local variable holds C(created dlhe), U(Updated dlhe), E(Record Exists with an open qual period), F for field validation failed
180          l_cre_upd_dlhe VARCHAR2(1);
181 
182          l_tot_ident_pop NUMBER ;     -- total identified students for target population
183 
184          l_new_dlhe_cnt  NUMBER;      -- Holds total new student DLHE records created
185          l_upd_dlhe_cnt  NUMBER;      -- Holds total student DLHE records updated
186          l_fail_std_cnt  NUMBER ;     -- Holds the number of students failed to satisfy the field validation
187          l_not_mod_cnt NUMBER;        -- Holds the total number of students not required to update/create student DLHE
188 
189   BEGIN
190 
191        -- Qualifying period is closed then delete associated student DLHE records with NST dlhe record status
192        IF p_closed_ind = 'Y' THEN
193            FOR cur_closed_dlhe_rec IN cur_closed_dlhe (p_submission_name,
194                                                        p_return_name,
195                                                        p_qual_period) LOOP
196                igs_he_stdnt_dlhe_pkg.delete_row(x_rowid => cur_closed_dlhe_rec.rowid);
197            END LOOP;
198        ELSE
199 
200               -- Initilazethe local variables
201               l_previous_person_id := -1;
202               l_cre_upd_dlhe  := NULL;
203               l_tot_ident_pop := 0;
204 
205               l_new_dlhe_cnt := 0;
206               l_upd_dlhe_cnt := 0;
207               l_fail_std_cnt := 0;
208               l_not_mod_cnt  := 0;
209 
210           -- qualifying period is L
211           IF p_qual_type = 'L' THEN
212 
213           -- Get the person_id and SPA details
214               FOR l_leavers_std_rec IN cur_leavers_std(p_qual_start_date,
215                                                        p_qual_end_date) LOOP
216                 -- Call the dlhe_process_spa process for each student program attempt
217                 -- If student have more than one SPA, and if student record created, updated or not required to edit in dlhe table for any SPA then
218                 -- skip to pass the successive SPAs else pass the next SPA,
219 
220                  IF l_previous_person_id <> l_leavers_std_rec.person_id OR l_cre_upd_dlhe = 'F' THEN
221 
222                        IF l_previous_person_id <> l_leavers_std_rec.person_id THEN
223 
224                IF l_cre_upd_dlhe = 'C' THEN               -- l_cre_upd_dlhe returned value C means student DLHE record created
225                               l_new_dlhe_cnt := l_new_dlhe_cnt +1;
226                            ELSIF l_cre_upd_dlhe = 'U'  THEN           -- l_cre_upd_dlhe returned value U means student DLHE record updated
227                               l_upd_dlhe_cnt := l_upd_dlhe_cnt + 1;
228                            ELSIF l_cre_upd_dlhe = 'F'  THEN           -- l_cre_upd_dlhe returned value F means student failed the field validation
229                               l_fail_std_cnt :=l_fail_std_cnt + 1;
230                            ELSIF l_cre_upd_dlhe ='E'  THEN            -- Student dlhe is not required to modify
231                               l_not_mod_cnt := l_not_mod_cnt + 1;
232                            END IF;
233 
234                END IF;
235 
236                        l_previous_person_id := l_leavers_std_rec.person_id;
237 
238                       igs_he_identify_target_pop.dlhe_process_spa(P_submission_name => p_submission_name,
239                                        p_return_name     => p_return_name,
240                                        p_qual_period     => p_qual_period,
241                                        P_qual_type       => 'L',
242                                        p_person_id       => l_leavers_std_rec.person_id,
243                                        p_course_cd       => l_leavers_std_rec.course_cd,
244                                        p_version_number  => l_leavers_std_rec.version_number,
245                                        p_cre_upd_dlhe    => l_cre_upd_dlhe
246                                      );
247 
248                   END IF;
249               END LOOP;  -- End loop for cur_leavers_std
250 
251                         -- For last student in the loop
252                         IF l_cre_upd_dlhe = 'C' THEN               -- l_cre_upd_dlhe returned value C means student DLHE record created
253                             l_new_dlhe_cnt := l_new_dlhe_cnt +1;
254                         ELSIF l_cre_upd_dlhe = 'U'  THEN           -- l_cre_upd_dlhe returned value U means student DLHE record updated
255                             l_upd_dlhe_cnt := l_upd_dlhe_cnt + 1;
256                         ELSIF l_cre_upd_dlhe = 'F'  THEN           -- l_cre_upd_dlhe returned value F means student failed the field validation
257                              l_fail_std_cnt :=l_fail_std_cnt + 1;
258                         ELSIF l_cre_upd_dlhe ='E'  THEN            -- Student dlhe is not required to modify
259                              l_not_mod_cnt := l_not_mod_cnt + 1;
260                         END IF;
261 
262                        -- total number of identified leavers students for the population
263                       l_tot_ident_pop := l_tot_ident_pop + l_new_dlhe_cnt + l_upd_dlhe_cnt + l_fail_std_cnt + l_not_mod_cnt;
264 
265                       -- Report the total number of Leaver students identifed in the population
266                       fnd_message.set_name('IGS','IGS_HE_DLHE_ST_IDENT_POP');
267                       fnd_message.set_token('TOTAL_STD_POP',l_tot_ident_pop );
268                       fnd_message.set_token('RETURN_NAME',p_return_name);
269                       fnd_message.set_token('QUAL_PERIOD',p_qual_period);
270                       fnd_file.put_line(fnd_file.log, fnd_message.get);
271 
272           ELSIF p_qual_type = 'R' THEN
273 
274               -- Get the research students and their SPAs
275               FOR l_research_std_rec IN cur_research_std  LOOP
276 
277                   -- Derive COMDATE field value for the student and check whether COMDATE value falls in between Qualification period start date and end date
278               l_comdate := NULL;
279                    igs_he_extract_fields_pkg.get_commencement_dt
280                                   ( p_hesa_commdate      =>  l_research_std_rec.hst_commencement_dt,
281                                     p_enstdnt_commdate   =>  l_research_std_rec.sca_commencement_dt,
282                                     p_person_id          =>  l_research_std_rec.person_id ,
283                                     p_course_cd          =>  l_research_std_rec.course_cd,
284                                     p_version_number     =>  l_research_std_rec.version_number,
285                                     p_student_inst_number => l_research_std_rec.student_inst_number,
286                                     p_final_commdate      => l_comdate);
287 
288                        -- Check whether the HESA COMDATE falls in between the qualifying period start date and end date,
289                        -- if student satisfies the condition then, he is eligible for DLHE return
290                        IF TO_DATE(l_comdate,'DD-MM-RRRR') >= p_qual_start_date AND
291                           TO_DATE(l_comdate,'DD-MM-RRRR') <= p_qual_end_date THEN
292 
293                          -- Call the dlhe_process_spa process for each student program attempt
294                          -- If student have more than one SPA, and if student record created, updated or not required to edit in dlhe table for any SPA then
295                          -- skip to pass successive SPAs else pass the next SPA,
296 
297                           IF l_previous_person_id <> l_research_std_rec.person_id OR l_cre_upd_dlhe = 'F' THEN
298 
299                               IF l_previous_person_id <> l_research_std_rec.person_id THEN
300 
301                                  IF l_cre_upd_dlhe = 'C' THEN               -- l_cre_upd_dlhe returned value C means student DLHE record created
302                                      l_new_dlhe_cnt := l_new_dlhe_cnt +1;
303                                  ELSIF l_cre_upd_dlhe = 'U'  THEN           -- l_cre_upd_dlhe returned value U means student DLHE record updated
304                                      l_upd_dlhe_cnt := l_upd_dlhe_cnt + 1;
305                                  ELSIF l_cre_upd_dlhe = 'F'  THEN           -- l_cre_upd_dlhe returned value F means student failed the field validation
306                                      l_fail_std_cnt :=l_fail_std_cnt + 1;
307                                  ELSIF l_cre_upd_dlhe ='E'  THEN            -- Student dlhe is not required to modify
308                                      l_not_mod_cnt := l_not_mod_cnt + 1;
309                                  END IF;
310 
311                               END IF;
312 
313                                 l_previous_person_id := l_research_std_rec.person_id;
314                                     -- Call the dlhe_process_spa procedure
315                                  igs_he_identify_target_pop.dlhe_process_spa(P_submission_name => p_submission_name,
316                                                 p_return_name     => p_return_name,
317                                                 p_qual_period     => p_qual_period,
318                                                 P_qual_type       => 'R',
319                                                 p_person_id       => l_research_std_rec.person_id,
320                                                 p_course_cd       => l_research_std_rec.course_cd,
321                                                 p_version_number  => l_research_std_rec.version_number,
322                                                 p_cre_upd_dlhe    => l_cre_upd_dlhe
323                                                );
324 
325                          END IF;
326                     END IF;
327               END LOOP;  -- End loop for l_research_std_rec
328 
329                         -- Count the last student details
330                         IF l_cre_upd_dlhe = 'C' THEN               -- l_cre_upd_dlhe returned value C means student DLHE record created
331                             l_new_dlhe_cnt := l_new_dlhe_cnt +1;
332                         ELSIF l_cre_upd_dlhe = 'U'  THEN           -- l_cre_upd_dlhe returned value U means student DLHE record updated
333                             l_upd_dlhe_cnt := l_upd_dlhe_cnt + 1;
334                         ELSIF l_cre_upd_dlhe = 'F'  THEN           -- l_cre_upd_dlhe returned value F means student failed the field validation
335                              l_fail_std_cnt :=l_fail_std_cnt + 1;
336                         ELSIF l_cre_upd_dlhe ='E'  THEN            -- Student dlhe is not required to modify
337                              l_not_mod_cnt := l_not_mod_cnt + 1;
338                         END IF;
339 
340                        -- total number of identified research students for the population
341                        l_tot_ident_pop := l_tot_ident_pop + l_new_dlhe_cnt + l_upd_dlhe_cnt + l_fail_std_cnt + l_not_mod_cnt;
342 
343                       -- Report the total number of research students identifed for target population
344                       fnd_message.set_name('IGS','IGS_HE_DLHE_ST_IDENT_POP');
345                       fnd_message.set_token('TOTAL_STD_POP',l_tot_ident_pop );
346                       fnd_message.set_token('RETURN_NAME',p_return_name);
347                       fnd_message.set_token('QUAL_PERIOD',p_qual_period);
348                       fnd_file.put_line(fnd_file.log, fnd_message.get);
349 
350           END IF;    -- End if for qual type
351 
352                -- Report the total number of new student DLHE records created
353               fnd_message.set_name('IGS','IGS_HE_DLHE_REC_CREATED');
354               fnd_message.set_token('CREATED_DLHE', l_new_dlhe_cnt);
355               fnd_message.set_token('RETURN_NAME',p_return_name);
356               fnd_message.set_token('QUAL_PERIOD',p_qual_period);
357               fnd_file.put_line(fnd_file.log, fnd_message.get);
358 
359               -- Report the total number of student DLHE records updated with the current qualifying period
360               fnd_message.set_name('IGS','IGS_HE_DLHE_REC_UPDATED');
361               fnd_message.set_token('UPDATED_DLHE', l_upd_dlhe_cnt);
362               fnd_message.set_token('RETURN_NAME',p_return_name);
363               fnd_message.set_token('QUAL_PERIOD',p_qual_period);
364               fnd_file.put_line(fnd_file.log, fnd_message.get);
365 
366                -- Report the total number of students failed to satisfy the field validations
367               fnd_message.set_name('IGS','IGS_HE_DLHE_FAILED_STD');
368               fnd_message.set_token('FAIL_DLHE', l_fail_std_cnt);
369               fnd_message.set_token('RETURN_NAME',p_return_name);
370               fnd_message.set_token('QUAL_PERIOD',p_qual_period);
371               fnd_file.put_line(fnd_file.log, fnd_message.get);
372 
373                -- Report the total number of students have the student DLHE records with open qualifying period,
374                -- for them not required to modify student DLHE record.
375               fnd_message.set_name('IGS','IGS_HE_DLHE_NOT_MODIFIED');
376               fnd_message.set_token('NOT_MOD', l_not_mod_cnt);
377               fnd_message.set_token('RETURN_NAME',p_return_name);
378               fnd_message.set_token('QUAL_PERIOD',p_qual_period);
379               fnd_file.put_line(fnd_file.log, fnd_message.get);
380 
381      END IF;  -- End if For closed qual_period
382 
383     EXCEPTION
384      WHEN OTHERS THEN
385         Fnd_Message.Set_Name('IGS','IGS_GE_UNHANDLED_EXP');
386         Fnd_Message.Set_Token('NAME','igs_he_identify_target_pop.dlhe_identify_spa');
387         fnd_file.put_line(fnd_file.log, fnd_message.get);
388         App_Exception.Raise_Exception;
389 
390   END  dlhe_identify_spa;
391 
392 
393   PROCEDURE dlhe_process_spa( P_submission_name IN  igs_he_sub_rtn_qual.submission_name%TYPE,
394                               p_return_name     IN  igs_he_sub_rtn_qual.return_name%TYPE,
395                               p_qual_period     IN  igs_he_sub_rtn_qual.qual_period_code%TYPE,
396                               P_qual_type       IN  igs_he_sub_rtn_qual.qual_period_type%TYPE,
397                               p_person_id       IN  igs_he_st_spa.person_id%TYPE,
398                               p_course_cd       IN  igs_he_st_spa.course_cd%TYPE,
399                               p_version_number  IN  igs_he_st_spa.version_number%TYPE,
400                               p_cre_upd_dlhe    OUT NOCOPY VARCHAR2
401                              ) IS
402  /******************************************************************
403   Created By      :  prasad marada
404   Date Created By :  20-Apr-2003
405   Purpose         :  For successfull student create/Update the student DLHE table
406                      in this procedure
407   Known limitations,enhancements,remarks:
408   Change History
409   Who       When         What
410  *******************************************************************/
411 
412           -- Cursor to get the Qualification details for validations and update the student dlhe table.
413           CURSOR cur_qual_dets (cp_submission_name   igs_he_sub_rtn_qual.submission_name%TYPE,
414                                 cp_return_name       igs_he_sub_rtn_qual.return_name%TYPE,
415                                 cp_qual_period_code  igs_he_sub_rtn_qual.qual_period_code%TYPE) IS
416           SELECT qual.qual_period_start_date,
417                  qual.qual_period_end_date,
418                  qual.user_return_subclass,
419                  qual.closed_ind
420           FROM igs_he_sub_rtn_qual  qual,
421                igs_he_usr_rtn_clas urc
422           WHERE qual.submission_name     = cp_submission_name
423             AND qual.return_name         = cp_return_name
424             AND qual.qual_period_code    = cp_qual_period_code
425             AND qual.user_return_subclass = urc.user_return_subclass
426             AND urc.system_return_class_type = 'DLHE';
427 
428           l_qual_dets  cur_qual_dets%ROWTYPE;
429 
430           -- Cursor to get the student DLHE record details for validations and for updateing Student DLHE table
431           CURSOR cur_stdnt_dlhe(cp_submission_name  igs_he_stdnt_dlhe.submission_name%TYPE,
432                                 cp_return_name      igs_he_stdnt_dlhe.return_name%TYPE,
433                                 cp_person_id        igs_he_stdnt_dlhe.person_id%TYPE)  IS
434           SELECT sdlhe.rowid,
435                  sdlhe.*
436           FROM igs_he_stdnt_dlhe sdlhe
437           WHERE sdlhe.submission_name = cp_submission_name
438             AND sdlhe.return_name     = cp_return_name
439             AND sdlhe.person_id       = cp_person_id;
440 
441           l_stdnt_dlhe_rec cur_stdnt_dlhe%ROWTYPE;
442 
443           l_include VARCHAR2(1);
444           l_qualified_teacher  VARCHAR2(1);
445           l_pt_study VARCHAR2(1);
446 
447           l_rowid VARCHAR2(30);
448 
449    BEGIN
450 
451            l_include := 'N';
452            l_qualified_teacher := 'N';
453            l_pt_study := 'N';
454 
455                  --Get the Qual details for further processing
456                  OPEN cur_qual_dets (p_submission_name,
457                                      p_return_name,
458                                      p_qual_period);
459                  FETCH cur_qual_dets INTO l_qual_dets;
460                  CLOSE cur_qual_dets;
461             -- Call the dlhe_review_spa procedure
462             igs_he_identify_target_pop.dlhe_review_spa(
463                              p_submission_name   => p_submission_name,
464                              p_return_name       => p_return_name,
465                              p_qual_period       => p_qual_period,
466                              p_qual_type         => p_qual_type,
467                              p_qual_start_dt     => l_qual_dets.qual_period_start_date,
468                              p_qual_end_dt       => l_qual_dets.qual_period_end_date,
469                              p_person_id         => p_person_id,
470                              p_course_cd         => p_course_cd,
471                              p_version_number    => p_version_number,
472                              p_include           => l_include,
473                              p_qualified_teacher => l_qualified_teacher,
474                              p_pt_study          => l_pt_study
475                             );
476 
477              -- dlhe_review_spa process returns include Y means, student satisfied the field validation and
478              -- eligible for target population
479             IF l_include = 'Y' THEN
480                  -- Check whether student have the student dlhe record ubder this submission
481                  OPEN cur_stdnt_dlhe (p_submission_name,
482                                       p_return_name,
483                                       p_person_id);
484                  FETCH cur_stdnt_dlhe INTO l_stdnt_dlhe_rec;
485                  -- If the student does not have the student DLHE record for the sublission then create new student DLHE record
486                  IF cur_stdnt_dlhe%NOTFOUND THEN
487                    -- Create student DLHE record
488 
489                     igs_he_stdnt_dlhe_pkg.insert_row(
490                                             x_rowid                      => l_rowid,
491                                             x_person_id                  => p_person_id,
492                                             x_submission_name            => p_submission_name,
493                                             x_user_return_subclass       => l_qual_dets.user_return_subclass,
494                                             x_return_name                => p_return_name,
495                                             x_qual_period_code           => p_qual_period,
496                                             x_dlhe_record_status         => 'NST',
497                                             x_participant_source         => 'I',
498                                             x_date_status_changed        => NULL,
499                                             x_validation_status          => NULL,
500                                             x_admin_coding               => NULL,
501                                             x_survey_method              => NULL,
502                                             x_employment                 => NULL,
503                                             x_further_study              => NULL,
504                                             x_qualified_teacher          => l_qualified_teacher,
505                                             x_pt_study                   => l_pt_study,
506                                             x_employer_business          => NULL,
507                                             x_employer_name              => NULL,
508                                             x_employer_classification    => NULL,
509                                             x_employer_location          => NULL,
510                                             x_employer_postcode          => NULL,
511                                             x_employer_country           => NULL,
512                                             x_job_title                  => NULL,
513                                             x_job_duties                 => NULL,
514                                             x_job_classification         => NULL,
515                                             x_employer_size              => NULL,
516                                             x_job_duration               => NULL,
517                                             x_job_salary                 => NULL,
518                                             x_salary_refused             => 'N',
519                                             x_qualification_requirement  => NULL,
520                                             x_qualification_importance   => NULL,
521                                             x_job_reason1                => 'N',
522                                             x_job_reason2                => 'N',
523                                             x_job_reason3                => 'N',
524                                             x_job_reason4                => 'N',
525                                             x_job_reason5                => 'N',
526                                             x_job_reason6                => 'N',
527                                             x_job_reason7                => 'N',
528                                             x_job_reason8                => 'N',
529                                             x_other_job_reason           => NULL,
530                                             x_no_other_job_reason        => 'N',
531                                             x_job_source                 => NULL,
532                                             x_other_job_source           => NULL,
533                                             x_no_other_job_source        => 'N',
534                                             x_previous_job               => NULL,
535                                             x_previous_jobtype1          => 'N',
536                                             x_previous_jobtype2          => 'N',
537                                             x_previous_jobtype3          => 'N',
538                                             x_previous_jobtype4          => 'N',
539                                             x_previous_jobtype5          => 'N',
540                                             x_previous_jobtype6          => 'N',
541                                             x_further_study_type         => NULL,
542                                             x_course_name                => NULL,
543                                             x_course_training_subject    => NULL,
544                                             x_research_subject           => NULL,
545                                             x_research_training_subject  => NULL,
546                                             x_further_study_provider     => NULL,
547                                             x_further_study_qualaim      => NULL,
548                                             x_professional_qualification => NULL,
549                                             x_study_reason1              => NULL,
550                                             x_study_reason2              => 'N',
551                                             x_study_reason3              => 'N',
552                                             x_study_reason4              => 'N',
553                                             x_study_reason5              => 'N',
554                                             x_study_reason6              => 'N',
555                                             x_study_reason7              => 'N',
556                                             x_other_study_reason         => NULL,
557                                             x_no_other_study_reason      => 'N',
558                                             x_employer_sponsored         => 'N',
559                                             x_funding_source             => NULL,
560                                             x_teacher_teaching           => 'N',
561                                             x_teacher_seeking            => 'N',
562                                             x_teaching_sector            => NULL,
563                                             x_teaching_level             => NULL,
564                                             x_reason_for_ptcourse        => NULL,
565                                             x_job_while_studying         => 'N',
566                                             x_employer_support1          => 'N',
567                                             x_employer_support2          => 'N',
568                                             x_employer_support3          => 'N',
569                                             x_employer_support4          => 'N',
570                                             x_employer_support5          => 'N',
571                                             x_popdlhe_flag               => 'N'
572                                           );
573                        -- Return C for successfully created student
574                        p_cre_upd_dlhe := 'C';
575                 ELSE
576                    -- If student have the Student DLHE record then check whether the qualifying period is closed or not
577                    OPEN cur_qual_dets (p_submission_name,
578                                        p_return_name,
579                                        l_stdnt_dlhe_rec.qual_period_code);
580                    FETCH cur_qual_dets INTO l_qual_dets;
581                    CLOSE cur_qual_dets;
582 
583                     -- If the student DLHE record qualifying period is closed then update Student DLHE record with current qualifying period
584                      IF l_qual_dets.closed_ind = 'Y' THEN
585                          -- Update the existing closed qualifying period with current qualifying period
586                          igs_he_stdnt_dlhe_pkg.update_row(
587                                             x_rowid                     => l_stdnt_dlhe_rec.rowid,
588                                             x_person_id                 => l_stdnt_dlhe_rec.person_id,
589                                             x_submission_name           => l_stdnt_dlhe_rec.submission_name,
590                                             x_user_return_subclass      => l_stdnt_dlhe_rec.user_return_subclass ,
591                                             x_return_name               => l_stdnt_dlhe_rec.return_name,
592                                             x_qual_period_code          => p_qual_period,
593                                             x_dlhe_record_status        => l_stdnt_dlhe_rec.dlhe_record_status,
594                                             x_participant_source        => l_stdnt_dlhe_rec.participant_source,
595                                             x_date_status_changed       => l_stdnt_dlhe_rec.date_status_changed,
596                                             x_validation_status         => l_stdnt_dlhe_rec.validation_status,
597                                             x_admin_coding              => l_stdnt_dlhe_rec.admin_coding,
598                                             x_survey_method             => l_stdnt_dlhe_rec.survey_method,
599                                             x_employment                => l_stdnt_dlhe_rec.employment,
600                                             x_further_study             => l_stdnt_dlhe_rec.further_study,
601                                             x_qualified_teacher         => l_stdnt_dlhe_rec.qualified_teacher,
602                                             x_pt_study                  => l_stdnt_dlhe_rec.pt_study,
603                                             x_employer_business         => l_stdnt_dlhe_rec.employer_business,
604                                             x_employer_name             => l_stdnt_dlhe_rec.employer_name,
605                                             x_employer_classification   => l_stdnt_dlhe_rec.employer_classification,
606                                             x_employer_location         => l_stdnt_dlhe_rec.employer_location,
607                                             x_employer_postcode         => l_stdnt_dlhe_rec.employer_postcode,
608                                             x_employer_country          => l_stdnt_dlhe_rec.employer_country,
609                                             x_job_title                 => l_stdnt_dlhe_rec.job_title,
610                                             x_job_duties                => l_stdnt_dlhe_rec.job_duties,
611                                             x_job_classification        => l_stdnt_dlhe_rec.job_classification,
612                                             x_employer_size             => l_stdnt_dlhe_rec.employer_size,
613                                             x_job_duration              => l_stdnt_dlhe_rec.job_duration,
614                                             x_job_salary                => l_stdnt_dlhe_rec.job_salary,
615                                             x_salary_refused            => l_stdnt_dlhe_rec.salary_refused,
616                                             x_qualification_requirement => l_stdnt_dlhe_rec.qualification_requirement,
617                                             x_qualification_importance  => l_stdnt_dlhe_rec.qualification_importance,
618                                             x_job_reason1               => l_stdnt_dlhe_rec.job_reason1,
619                                             x_job_reason2               => l_stdnt_dlhe_rec.job_reason2,
620                                             x_job_reason3               => l_stdnt_dlhe_rec.job_reason3,
621                                             x_job_reason4               => l_stdnt_dlhe_rec.job_reason4,
622                                             x_job_reason5               => l_stdnt_dlhe_rec.job_reason5,
623                                             x_job_reason6               => l_stdnt_dlhe_rec.job_reason6,
624                                             x_job_reason7               => l_stdnt_dlhe_rec.job_reason7,
625                                             x_job_reason8               => l_stdnt_dlhe_rec.job_reason8,
626                                             x_other_job_reason          => l_stdnt_dlhe_rec.other_job_reason,
627                                             x_no_other_job_reason       => l_stdnt_dlhe_rec.no_other_job_reason,
628                                             x_job_source                => l_stdnt_dlhe_rec.job_source,
629                                             x_other_job_source          => l_stdnt_dlhe_rec.other_job_source,
630                                             x_no_other_job_source       => l_stdnt_dlhe_rec.no_other_job_source,
631                                             x_previous_job              => l_stdnt_dlhe_rec.previous_job,
632                                             x_previous_jobtype1         => l_stdnt_dlhe_rec.previous_jobtype1,
633                                             x_previous_jobtype2         => l_stdnt_dlhe_rec.previous_jobtype2,
634                                             x_previous_jobtype3         => l_stdnt_dlhe_rec.previous_jobtype3,
635                                             x_previous_jobtype4         => l_stdnt_dlhe_rec.previous_jobtype4,
636                                             x_previous_jobtype5         => l_stdnt_dlhe_rec.previous_jobtype5,
637                                             x_previous_jobtype6         => l_stdnt_dlhe_rec.previous_jobtype6,
638                                             x_further_study_type        => l_stdnt_dlhe_rec.further_study_type,
639                                             x_course_name               => l_stdnt_dlhe_rec.course_name,
640                                             x_course_training_subject   => l_stdnt_dlhe_rec.course_training_subject,
641                                             x_research_subject          => l_stdnt_dlhe_rec.research_subject,
642                                             x_research_training_subject => l_stdnt_dlhe_rec.research_training_subject,
643                                             x_further_study_provider    => l_stdnt_dlhe_rec.further_study_provider,
644                                             x_further_study_qualaim     => l_stdnt_dlhe_rec.further_study_qualaim,
645                                             x_professional_qualification=> l_stdnt_dlhe_rec.professional_qualification,
646                                             x_study_reason1             => l_stdnt_dlhe_rec.study_reason1,
647                                             x_study_reason2             => l_stdnt_dlhe_rec.study_reason2,
648                                             x_study_reason3             => l_stdnt_dlhe_rec.study_reason3,
649                                             x_study_reason4             => l_stdnt_dlhe_rec.study_reason4,
650                                             x_study_reason5             => l_stdnt_dlhe_rec.study_reason5,
651                                             x_study_reason6             => l_stdnt_dlhe_rec.study_reason6,
652                                             x_study_reason7             => l_stdnt_dlhe_rec.study_reason7,
653                                             x_other_study_reason        => l_stdnt_dlhe_rec.other_study_reason,
654                                             x_no_other_study_reason     => l_stdnt_dlhe_rec.no_other_study_reason,
655                                             x_employer_sponsored        => l_stdnt_dlhe_rec.employer_sponsored,
656                                             x_funding_source            => l_stdnt_dlhe_rec.funding_source,
657                                             x_teacher_teaching          => l_stdnt_dlhe_rec.teacher_teaching,
658                                             x_teacher_seeking           => l_stdnt_dlhe_rec.teacher_seeking,
659                                             x_teaching_sector           => l_stdnt_dlhe_rec.teaching_sector,
660                                             x_teaching_level            => l_stdnt_dlhe_rec.teaching_level,
661                                             x_reason_for_ptcourse       => l_stdnt_dlhe_rec.reason_for_ptcourse,
662                                             x_job_while_studying        => l_stdnt_dlhe_rec.job_while_studying,
663                                             x_employer_support1         => l_stdnt_dlhe_rec.employer_support1,
664                                             x_employer_support2         => l_stdnt_dlhe_rec.employer_support2,
665                                             x_employer_support3         => l_stdnt_dlhe_rec.employer_support3,
666                                             x_employer_support4         => l_stdnt_dlhe_rec.employer_support4,
667                                             x_employer_support5         => l_stdnt_dlhe_rec.employer_support5,
668                                             x_popdlhe_flag              => l_stdnt_dlhe_rec.popdlhe_flag
669                                            );
670                               -- Return U means updated the record with current qualifying period successfully
671                                p_cre_upd_dlhe := 'U';
672                      ELSE
673                          -- Return E means not required to update the record, there exists student DLHE record with an open qualifying period
674                          p_cre_upd_dlhe := 'E';
675                      END IF;    -- End if for closed Y
676                  END IF;     -- end if for cur_stdnt_dlhe%NOTFOUND
677                  CLOSE cur_stdnt_dlhe;
678             ELSE
679                -- Return F means, student failed to satisfy the Field validation
680                p_cre_upd_dlhe := 'F';
681             END IF;    -- End if for include N
682 
683    EXCEPTION
684      WHEN OTHERS THEN
685         Fnd_Message.Set_Name('IGS','IGS_GE_UNHANDLED_EXP');
686         Fnd_Message.Set_Token('NAME','igs_he_identify_target_pop.dlhe_process_spa');
687         fnd_file.put_line(fnd_file.log, fnd_message.get);
688         App_Exception.Raise_Exception;
689 
690   END dlhe_process_spa;
691 
692   PROCEDURE dlhe_review_spa( p_submission_name   IN  igs_he_sub_rtn_qual.submission_name%TYPE,
693                              p_return_name       IN  igs_he_sub_rtn_qual.return_name%TYPE,
694                              p_qual_period       IN  igs_he_sub_rtn_qual.qual_period_code%TYPE,
695                              P_qual_type         IN  igs_he_sub_rtn_qual.qual_period_type%TYPE,
696                              p_qual_start_dt     IN  igs_he_sub_rtn_qual.qual_period_start_date%TYPE,
697                              p_qual_end_dt       IN  igs_he_sub_rtn_qual.qual_period_end_date%TYPE,
698                              p_person_id         IN  igs_he_st_spa.person_id%TYPE,
699                              p_course_cd         IN  igs_he_st_spa.course_cd%TYPE,
700                              p_version_number    IN  igs_he_st_spa.version_number%TYPE,
701                              p_include           OUT NOCOPY VARCHAR2,
702                              p_qualified_teacher OUT NOCOPY VARCHAR2,
703                              p_pt_study          OUT NOCOPY VARCHAR2
704                           )  IS
705  /******************************************************************
706   Created By      :  prasad marada
707   Date Created By :  20-Apr-2003
708   Purpose         :  Derive the Field value for each student and check whether the
709                      can be includeed in the target population or not.
710   Known limitations,enhancements,remarks:
711   Change History
712   Who       When         What
713   smaddali 09-dec-2003  Modified logic to get Term record details for HECR214 - Term based fees enhancement, bug#3291656
714   ayedubat 15-dec-2003  Modified the cursor, c_yop_susa to add a new validation based on the
715                         HESA Submission Period Start Date and end date for bug# 3288836
716   jbaber   01-sep-2005  Modified for HE310 - Load DLHE Target Population
717                         - Removed QualAim check for Reseach students
718                         - Added new european countries to allowed domicile codes for Leaver students
719  *******************************************************************/
720 
721             -- Get the reporting dates for the submission
722            CURSOR cur_he_sub_header (cp_submission_name igs_he_submsn_header.submission_name%TYPE) IS
723            SELECT enrolment_start_date,
724                   enrolment_end_date
725            FROM igs_he_submsn_header
726            WHERE submission_name = cp_submission_name ;
727 
728             l_he_sub_header cur_he_sub_header%ROWTYPE;
729 
730             -- Get the Location of study, for deriving LOCSDY (71) value
731            CURSOR cur_he_st_prog (cp_course_cd      igs_he_st_prog.course_cd%TYPE,
732                                   cp_version_number igs_he_st_prog.version_number%TYPE) IS
733            SELECT location_of_study
734            FROM igs_he_st_prog
735            WHERE course_cd    = cp_course_cd
736            AND version_number = cp_version_number;
737 
738            l_he_st_prog  cur_he_st_prog%ROWTYPE;
739 
740            -- Get the SUSA details for deriving MODE, LOCSDY and MSTUFEE field values
741            CURSOR c_yop_susa (cp_person_id  igs_as_su_setatmpt.person_id%TYPE,
742                               cp_course_cd  igs_as_su_setatmpt.course_cd%TYPE,
743                               cp_enrl_start_dt igs_he_submsn_header.enrolment_start_date%TYPE,
744                               cp_enrl_end_dt igs_he_submsn_header.enrolment_end_date%TYPE) IS
745            SELECT DISTINCT susa.unit_set_cd,
746                   susa.us_version_number,
747                   susa.sequence_number,
748                   susa.rqrmnts_complete_dt,
749                   susa.selection_dt,
750                   susa.end_dt,
751                   husa.study_mode,
752                   husa.study_location ,
753                   husa.student_fee
754            FROM  igs_as_su_setatmpt  susa,
755                  igs_he_en_susa      husa,
756                  igs_en_unit_set     us,
757                  igs_en_unit_set_cat susc,
758                  igs_en_stdnt_ps_att   sca
759            WHERE susa.person_id         = sca.person_id
760            AND   susa.course_cd         = sca.course_cd
761            AND   susa.person_id         = cp_person_id
762            AND   susa.course_cd         = cp_course_cd
763            AND   susa.unit_set_cd       = husa.unit_set_cd
764            AND   susa.us_version_number = husa.us_version_number
765            AND   susa.person_id         = husa.person_id
766            AND   susa.course_cd         = husa.course_cd
767            AND   susa.sequence_number   = husa.sequence_number
768            AND   susa.unit_set_cd       = us.unit_set_cd
769            AND   susa.us_version_number = us.version_number
770            AND   us.unit_set_cat        = susc.unit_set_cat
771            AND   susc.s_unit_set_cat    = 'PRENRL_YR'
772            AND   (susa.selection_dt <= cp_enrl_end_dt AND
773                   (susa.end_dt  IS NULL OR susa.end_dt  >= cp_enrl_start_dt ) AND
774                   (susa.rqrmnts_complete_dt IS NULL OR susa.rqrmnts_complete_dt >= cp_enrl_start_dt))
775            ORDER BY susa.rqrmnts_complete_dt DESC, susa.end_dt DESC, susa.selection_dt DESC;
776 
777            l_yop_susa  c_yop_susa%ROWTYPE;
778 
779            -- Get the Student program attempt details for deriving MODE, RSNLEAVE, DOMICILE, QUALAIM etc
780            CURSOR c_spa (cp_person_id  igs_en_stdnt_ps_att.person_id%TYPE,
781                          cp_course_cd  igs_en_stdnt_ps_att.course_cd%TYPE)IS
782            SELECT sca.version_number,
783                   sca.cal_type,
784                   sca.location_cd ,
785                   sca.attendance_mode,
786                   sca.attendance_type,
787                   sca.commencement_dt  sca_commencement_dt,
788                   sca.discontinued_dt,
789                   sca.discontinuation_reason_cd,
790                   sca.course_rqrmnt_complete_ind,
791                   sca.course_rqrmnts_complete_dt,
792                   sca.adm_admission_appl_number,
793                   sca.adm_nominated_course_cd,
794                   sca.adm_sequence_number,
795                   hspa.domicile_cd,
796                   hspa.commencement_dt hspa_commencement_dt,
797                   hspa.special_student,
798                   hspa.student_qual_aim,
799                   hspa.student_inst_number
800            FROM   igs_en_stdnt_ps_att   sca,
801                   igs_he_st_spa         hspa
802            WHERE  sca.person_id  = cp_person_id
803            AND    sca.course_cd  = cp_course_cd
804            AND    sca.person_id  = hspa.person_id
805            AND    sca.course_cd  = hspa.course_cd;
806 
807            l_spa c_spa%ROWTYPE;
808 
809            -- Get the location of study and mode of study for deriving LOCSDY and MODE values
810            CURSOR cur_he_poous(cp_course_cd          igs_he_poous.course_cd%TYPE,
811                                cp_version_number     igs_he_poous.crv_version_number%TYPE,
812                                cp_cal_type           igs_he_poous.cal_type%TYPE,
813                                cp_location_cd        igs_he_poous.location_cd%TYPE,
814                                cp_attendance_mode    igs_he_poous.attendance_mode%TYPE,
815                                cp_attendance_type    igs_he_poous.attendance_type%TYPE,
816                                cp_unit_set_cd        igs_he_poous.unit_set_cd%TYPE,
817                                cp_us_version_number  igs_he_poous.us_version_number%TYPE) IS
818            SELECT  location_of_study,
819                    mode_of_study
820            FROM   igs_he_poous
821            WHERE course_cd          = cp_course_cd
822             AND  crv_version_number = cp_version_number
823             AND  cal_type           = cp_cal_type
824             AND  location_cd        = cp_location_cd
825             AND  attendance_mode    = cp_attendance_mode
826             AND  attendance_type    = cp_attendance_type
827             AND  unit_set_cd        = cp_unit_set_cd
828             AND  us_version_number  = cp_us_version_number;
829 
830             l_he_poous cur_he_poous%ROWTYPE;
831 
832            -- get the domicile code and special student code from igs_he_ad_dtl
833            CURSOR c_he_ad_dtl (cp_person_id              igs_he_ad_dtl.person_id%TYPE,
834                                cp_admission_appl_number  igs_he_ad_dtl.admission_appl_number%TYPE,
835                                cp_nominated_course_cd    igs_he_ad_dtl.nominated_course_cd%TYPE ,
836                                cp_sequence_number        igs_he_ad_dtl.sequence_number%TYPE) IS
837            SELECT  domicile_cd,
838                    special_student_cd
839            FROM   igs_he_ad_dtl
840            WHERE  person_id             = cp_person_id
841            AND    admission_appl_number = cp_admission_appl_number
842            AND    nominated_course_cd   = cp_nominated_course_cd
843            AND    sequence_number       = cp_sequence_number;
844 
845            l_he_ad_dtl c_he_ad_dtl%ROWTYPE;
846 
847             -- Get the person number for reporting into log file
848            CURSOR cur_person_num (cp_person_id  igs_pe_person_base_v.person_id%TYPE) IS
849            SELECT person_number
850            FROM igs_pe_person_base_v
851            WHERE person_id = cp_person_id;
852 
853            l_person_number igs_pe_person_base_v.person_number%TYPE;
854 
855              -- QUAL1 and QUAL2 out parameter/local variables
856             l_oss_qual1   igs_he_ex_rn_dat_fd.value%TYPE;
857             l_oss_qual2   igs_he_ex_rn_dat_fd.value%TYPE;
858             l_hesa_qual1  igs_he_ex_rn_dat_fd.value%TYPE;
859             l_hesa_qual2  igs_he_ex_rn_dat_fd.value%TYPE;
860             l_hesa_classification igs_he_ex_rn_dat_fd.value%TYPE;
861 
862              -- LOCSDY out parameter/local variables
863             l_oss_locsdy    igs_he_ex_rn_dat_fd.value%TYPE;
864             l_hesa_locsdy   igs_he_ex_rn_dat_fd.value%TYPE;
865 
866              -- RSNLEAVE out parameter/local variables
867             l_rsn_inst_left    igs_he_ex_rn_dat_fd.value%TYPE;
868 
869              -- DOMICILE out parameter/local variables
870             l_hesa_domicile   igs_he_ex_rn_dat_fd.value%TYPE;
871 
872               -- MODE out parameter/local variables
873             l_mode  igs_he_ex_rn_dat_fd.value%TYPE;
874 
875              -- Special Student out parameter/local variables
876             l_oss_special_student  igs_he_ex_rn_dat_fd.value%TYPE;
877             l_hesa_special_student  igs_he_ex_rn_dat_fd.value%TYPE;
878 
879               -- MSTUFEE out parameter/local variables
880             l_hesa_mstufee  igs_he_ex_rn_dat_fd.value%TYPE;
881 
882             l_include VARCHAR2(1);
883             l_qualified_teacher VARCHAR2(1);
884             l_pt_study VARCHAR2(1);
885 
886       -- smaddali added following cursors for HECR214 - term based fees enhancement build, bug#3291656
887 
888       -- Get the latest Term record for the Leavers,where the student left date lies between term start and end dates
889       CURSOR c_term_lev( cp_person_id  igs_en_spa_terms.person_id%TYPE,
890                           cp_course_cd  igs_en_spa_terms.program_cd%TYPE,
891                           cp_lev_dt  DATE ) IS
892       SELECT  tr.program_version , tr.acad_cal_type, tr.location_cd, tr.attendance_mode, tr.attendance_type
893       FROM  igs_en_spa_terms tr , igs_ca_inst_all ca
894       WHERE  tr.term_cal_type = ca.cal_type AND
895              tr.term_sequence_number = ca.sequence_number AND
896              tr.person_id = cp_person_id AND
897              tr.program_cd = cp_course_cd AND
898              cp_lev_dt BETWEEN ca.start_dt AND ca.end_dt
899       ORDER BY  ca.start_dt DESC;
900       c_term_lev_rec   c_term_lev%ROWTYPE ;
901 
902       -- Get the latest term record for the Continuing students, where the term start date lies in the HESA submission period
903       CURSOR c_term_con ( cp_person_id          igs_en_spa_terms.person_id%TYPE,
904                           cp_course_cd          igs_en_spa_terms.program_cd%TYPE,
905                           cp_sub_start_dt       igs_he_submsn_header.enrolment_start_date%TYPE ,
906                           cp_sub_end_dt         igs_he_submsn_header.enrolment_end_date%TYPE) IS
907       SELECT  tr.program_version , tr.acad_cal_type, tr.location_cd, tr.attendance_mode, tr.attendance_type
908       FROM  igs_en_spa_terms tr , igs_ca_inst_all ca
909       WHERE  tr.term_cal_type = ca.cal_type AND
910              tr.term_sequence_number = ca.sequence_number AND
911              tr.person_id = cp_person_id AND
912              tr.program_cd = cp_course_cd AND
913              ca.start_dt BETWEEN cp_sub_start_dt AND cp_sub_end_dt
914       ORDER BY  ca.start_dt DESC;
915       c_term_con_rec    c_term_con%ROWTYPE ;
916       l_lev_dt   igs_en_stdnt_ps_att_all.discontinued_dt%TYPE ;
917 
918    BEGIN
919 
920          -- Get the values to be used as parameters to call HESA field derivation procedures
921          -- Get the reporting dates
922          l_he_sub_header        := NULL ;
923          OPEN cur_he_sub_header (p_submission_name) ;
924          FETCH cur_he_sub_header INTO l_he_sub_header;
925          CLOSE cur_he_sub_header;
926 
927          -- get yop details
928          l_yop_susa     := NULL ;
929          OPEN c_yop_susa (p_person_id,
930                           p_course_cd,
931                           l_he_sub_header.enrolment_start_date,
932                           l_he_sub_header.enrolment_end_date ) ;
933          FETCH c_yop_susa INTO l_yop_susa;
934          CLOSE c_yop_susa;
935 
936          -- Get the SPA details
937          l_spa  := NULL ;
938          OPEN c_spa (p_person_id,
939                      p_course_cd) ;
940          FETCH c_spa INTO l_spa;
941          CLOSE c_spa;
942 
943            -- smaddali added following code for HECR214 - term based fees enhancement build , Bug#3291656
944            -- to get version_number,cal_type,location_cd, attendance_type and mode from the Term record
945            -- Get the Leaving date for the student
946            l_lev_dt     := NULL;
947            l_lev_dt       := NVL(l_spa.course_rqrmnts_complete_dt,l_spa.discontinued_dt) ;
948 
949            -- For Leavers students the following is the logic
950            IF P_qual_type = 'L' THEN
951                 -- get the latest term record within which the Leaving date falls
952                       c_term_lev_rec        := NULL ;
953                       OPEN c_term_lev (p_person_id, p_course_cd, l_lev_dt );
954                       FETCH c_term_lev INTO c_term_lev_rec ;
955                       IF c_term_lev%FOUND THEN
956                              -- Override the location_cd,cal_type,version_number,attendance_type,attendance_mode
957                              -- in the SCA record with the term record values
958                              l_spa.version_number       := c_term_lev_rec.program_version ;
959                              l_spa.cal_type             := c_term_lev_rec.acad_cal_type ;
960                              l_spa.location_cd          := c_term_lev_rec.location_cd ;
961                              l_spa.attendance_mode      := c_term_lev_rec.attendance_mode ;
962                              l_spa.attendance_type      := c_term_lev_rec.attendance_type ;
963                       END IF ;
964                       CLOSE c_term_lev ;
965 
966            -- For Research students the following is the logic
967            ELSIF P_qual_type = 'R' THEN
968                 -- If the research student is a leaver(i.e leaving date falls within the Qualifying period)
969                 -- then get the latest term rec where the leaving date falls within the term calendar start and end dates
970                 IF  l_lev_dt BETWEEN p_qual_start_dt AND p_qual_end_dt THEN
971                       c_term_lev_rec        := NULL ;
972                       OPEN c_term_lev (p_person_id, p_course_cd, l_lev_dt );
973                       FETCH c_term_lev INTO c_term_lev_rec ;
974                       IF c_term_lev%FOUND THEN
975                              -- Override the location_cd,cal_type,version_number,attendance_type,attendance_mode
976                              -- in the SCA record with the term record values
977                              l_spa.version_number       := c_term_lev_rec.program_version ;
978                              l_spa.cal_type             := c_term_lev_rec.acad_cal_type ;
979                              l_spa.location_cd          := c_term_lev_rec.location_cd ;
980                              l_spa.attendance_mode      := c_term_lev_rec.attendance_mode ;
981                              l_spa.attendance_type      := c_term_lev_rec.attendance_type ;
982                       END IF ;
983                       CLOSE c_term_lev ;
984 
985                 -- Else the student is continuing student then get the latest term rec
986                 -- where the Term start date falls within the HESA Submission start and end dates
987                 ELSE
988                         -- Get the latest term record which falls within the FTE period and term start date > commencement dt
989                         c_term_con_rec  := NULL ;
990                         OPEN c_term_con(p_person_id, p_course_cd,l_he_sub_header.enrolment_start_date,l_he_sub_header.enrolment_end_date);
991                         FETCH c_term_con INTO c_term_con_rec ;
992                         IF c_term_con%FOUND THEN
993                              -- Override the location_cd,cal_type,version_number,attendance_type,attendance_mode
994                              -- in the SCA record with the term record values
995                              l_spa.version_number       := c_term_con_rec.program_version ;
996                              l_spa.cal_type             := c_term_con_rec.acad_cal_type ;
997                              l_spa.location_cd          := c_term_con_rec.location_cd ;
998                              l_spa.attendance_mode      := c_term_con_rec.attendance_mode ;
999                              l_spa.attendance_type      := c_term_con_rec.attendance_type ;
1000                         END IF ;
1001                         CLOSE c_term_con ;
1002                 END IF ; -- if student is leaving / continuing
1003 
1004            END IF;   -- if qualifying type is L/R
1005 
1006          -- get the poous details
1007          -- smaddali modified call to this cursor to pass l_spa.version_number instead of p_version_number
1008          -- as part of HECR214 - term based fees enhancement, Bug#3291656
1009          l_he_poous     := NULL ;
1010          OPEN  cur_he_poous (p_course_cd,
1011                              l_spa.version_number,
1012                              l_spa.cal_type,
1013                              l_spa.location_cd,
1014                              l_spa.attendance_mode,
1015                              l_spa.attendance_type,
1016                              l_yop_susa.unit_set_cd,
1017                              l_yop_susa.us_version_number);
1018          FETCH cur_he_poous INTO l_he_poous;
1019          CLOSE cur_he_poous;
1020 
1021          -- get the he admission details
1022          l_he_ad_dtl    := NULL ;
1023          OPEN c_he_ad_dtl (p_person_id,
1024                            l_spa.adm_admission_appl_number,
1025                            l_spa.adm_nominated_course_cd,
1026                            l_spa.adm_sequence_number);
1027          FETCH c_he_ad_dtl INTO l_he_ad_dtl ;
1028          CLOSE c_he_ad_dtl;
1029 
1030          --Get the person number for reporting purpose
1031          l_person_number        := NULL ;
1032          OPEN cur_person_num (p_person_id);
1033          FETCH cur_person_num INTO l_person_number;
1034          CLOSE cur_person_num;
1035 
1036      p_include := 'Y';
1037 
1038            -- For Leavers students the following is the logic
1039            IF P_qual_type = 'L' THEN
1040 
1041               -- Derive the QUAL1, QUAL2, LOCSDY, RSNLEAVE, DOMICILE and MODE field values
1042                        l_oss_qual1  := NULL;
1043                        l_oss_qual2  := NULL;
1044                        l_hesa_qual1 := NULL;
1045                        l_hesa_qual2 := NULL;
1046                        l_hesa_classification := NULL;
1047 
1048           -- Derive the QUAL1 (37) and QUAL2 (38) field values,
1049                  igs_he_extract_fields_pkg.get_qual_obtained
1050                       (p_person_id      =>  p_person_id,
1051                        p_course_cd      =>  p_course_cd,
1052                        p_enrl_start_dt  =>  l_he_sub_header.enrolment_start_date,
1053                        p_enrl_end_dt    =>  l_he_sub_header.enrolment_end_date,
1054                        p_oss_qual_obt1  =>  l_oss_qual1,
1055                        p_oss_qual_obt2  =>  l_oss_qual2,
1056                        p_hesa_qual_obt1 =>  l_hesa_qual1,
1057                        p_hesa_qual_obt2 =>  l_hesa_qual2,
1058                        p_classification =>  l_hesa_classification);
1059 
1060                      IF  l_hesa_qual1 IS NULL AND l_hesa_qual2 IS NULL THEN
1061                             p_include:= 'N';
1062                            fnd_message.set_name('IGS','IGS_HE_QUAL_FAIL_TO_DERIVE');
1063                            fnd_message.set_token('PERSON_NUMBER', l_person_number);
1064                            fnd_message.set_token('COURSE', p_course_cd);
1065                            fnd_file.put_line(fnd_file.log, fnd_message.get);
1066                  ELSIF (l_hesa_qual1 IS NULL OR l_hesa_qual1 NOT IN ('02','03','04','05','06','07','08','12','13','14','18','20','21','22','23','28','29','30','33','41','42') )
1067                         AND (l_hesa_qual2 IS NULL OR l_hesa_qual2 NOT IN ('02','03','04','05','06','07','08','12','13','14','18','20','21','22','23','28','29','30','33','41','42')) THEN
1068                             --Person failed to satisfy the qualification field validation, so report it in the log file
1069                             p_include:= 'N';
1070                             fnd_message.set_name('IGS','IGS_HE_QUAL_VALID_FAILED');
1071                             fnd_message.set_token('PERSON_NUMBER', l_person_number);
1072                             fnd_message.set_token('COURSE', p_course_cd);
1073                             fnd_message.set_token('QUAL1', l_hesa_qual1 );
1074                             fnd_message.set_token('QUAL2', l_hesa_qual2);
1075                             fnd_file.put_line(fnd_file.log, fnd_message.get);
1076                       END IF;
1077 
1078                       -- Get the location_of_study
1079                       -- smaddali modified call to this cursor to pass l_spa.version_number instead of p_version_number
1080                       -- as part of HECR214 - term based fees enhancement, Bug#3291656
1081                       l_he_st_prog      := NULL ;
1082                       OPEN cur_he_st_prog (p_course_cd,
1083                                            l_spa.version_number) ;
1084                       FETCH cur_he_st_prog INTO l_he_st_prog;
1085                       CLOSE cur_he_st_prog;
1086 
1087                         l_oss_locsdy := NULL;
1088                         l_hesa_locsdy := NULL;
1089 
1090                     -- Derive the LOCSDY (Field 71) value
1091                    igs_he_extract_fields_pkg.get_study_location (
1092                              p_susa_study_location  => l_yop_susa.study_location,
1093                              p_poous_study_location => l_he_poous.location_of_study,
1094                              p_prg_study_location   => l_he_st_prog.location_of_study,
1095                              p_oss_study_location   => l_oss_locsdy,
1096                              p_hesa_study_location  => l_hesa_locsdy);
1097 
1098                         -- If field value null or field value is not in the list then report the message in the log file
1099                        IF l_hesa_locsdy IS NULL THEN
1100                            p_include:= 'N';
1101                           fnd_message.set_name('IGS','IGS_HE_LOCSDY_FAIL_TO_DERIVE');
1102                           fnd_message.set_token('PERSON_NUMBER', l_person_number);
1103                           fnd_message.set_token('COURSE', p_course_cd);
1104                           fnd_file.put_line(fnd_file.log, fnd_message.get);
1105                        ELSIF  l_hesa_locsdy = '7' THEN
1106                             p_include:= 'N';
1107                           fnd_message.set_name('IGS','IGS_HE_LOCSDY_VALID_FAILED');
1108                           fnd_message.set_token('PERSON_NUMBER', l_person_number);
1109                           fnd_message.set_token('COURSE', p_course_cd);
1110                           fnd_message.set_token('LOCSDY', l_hesa_locsdy);
1111                           fnd_file.put_line(fnd_file.log, fnd_message.get);
1112                        END IF;
1113 
1114            -- Derive RSNLEAVE (field 33) value
1115                    l_rsn_inst_left := NULL;
1116                    igs_he_extract_fields_pkg.get_rsn_inst_left(
1117                             p_person_id        =>  p_person_id,
1118                             p_course_cd        =>  P_course_cd,
1119                             p_crs_req_comp_ind =>  l_spa.course_rqrmnt_complete_ind,
1120                             p_crs_req_comp_dt  =>  l_spa.course_rqrmnts_complete_dt,
1121                             p_disc_reason_cd   =>  l_spa.discontinuation_reason_cd,
1122                             p_disc_dt          =>  l_spa.discontinued_dt,
1123                             p_enrl_start_dt    =>  l_he_sub_header.enrolment_start_date,
1124                             p_enrl_end_dt      =>  l_he_sub_header.enrolment_end_date,
1125                             p_rsn_inst_left    =>  l_rsn_inst_left);
1126 
1127                          -- If the field value is not in the list then report the message in log file
1128                          IF l_rsn_inst_left = '05' THEN
1129                              p_include:= 'N';
1130                             fnd_message.set_name('IGS','IGS_HE_RSNLEAVE_VALID_FAILED');
1131                             fnd_message.set_token('PERSON_NUMBER', l_person_number);
1132                             fnd_message.set_token('COURSE', p_course_cd);
1133                             fnd_message.set_token('RSNLEAVE', l_rsn_inst_left);
1134                             fnd_file.put_line(fnd_file.log, fnd_message.get);
1135                          END IF;
1136 
1137                        -- Derive DOMICILE (Field 12) value
1138                           l_hesa_domicile := NULL;
1139                     igs_he_extract_fields_pkg.get_domicile(
1140                            p_ad_domicile    => l_he_ad_dtl.domicile_cd,
1141                            p_spa_domicile   => l_spa.domicile_cd,
1142                            p_hesa_domicile  => l_hesa_domicile);
1143 
1144                          -- If field value is null or field value is not in the list then report the message in log file
1145                          IF l_hesa_domicile IS NULL THEN
1146                               p_include:= 'N';
1147                              fnd_message.set_name('IGS','IGS_HE_DOMICILE_FAIL_TO_DERIVE');
1148                              fnd_message.set_token('PERSON_NUMBER', l_person_number);
1149                              fnd_message.set_token('COURSE', p_course_cd);
1150                              fnd_file.put_line(fnd_file.log, fnd_message.get);
1151                          ELSIF l_hesa_domicile NOT IN ('1610','1614','1641','1651','1653','1656','1659','1661','1676','1678','1693',
1152                                           '1710','1728','1751','1755','3826','4826','5826','6826','7826','8826',
1153                                           '1638','1639','1670','1700','1727','1831','1832','1833','1835','1850') THEN
1154                              p_include:= 'N';
1155                             fnd_message.set_name('IGS','IGS_HE_DOMICILE_VALID_FAILED');
1156                             fnd_message.set_token('PERSON_NUMBER', l_person_number);
1157                             fnd_message.set_token('COURSE', p_course_cd);
1158                             fnd_message.set_token('DOMICILE', l_hesa_domicile);
1159                             fnd_file.put_line(fnd_file.log, fnd_message.get);
1160                          END IF;
1161 
1162            -- Derive MODE (70) field value
1163                      l_mode := NULL;
1164                    igs_he_extract_fields_pkg.get_mode_of_study
1165                               (p_person_id         =>  p_person_id,
1166                                p_course_cd         =>  P_course_cd,
1167                                p_version_number    =>  p_version_number,
1168                                p_enrl_start_dt     =>  l_he_sub_header.enrolment_start_date,
1169                                p_enrl_end_dt       =>  l_he_sub_header.enrolment_end_date,
1170                                p_susa_study_mode   =>  l_yop_susa.study_mode,
1171                                p_poous_study_mode  =>  l_he_poous.mode_of_study,
1172                                p_attendance_type   =>  l_spa.attendance_type,
1173                                p_mode_of_study     =>  l_mode);
1174 
1175                          -- If field value is null or field value is not in the list then report the message in log file
1176                         IF l_mode IS NULL THEN
1177                              p_include:= 'N';
1178                             fnd_message.set_name('IGS','IGS_HE_MODE_FAIL_TO_DERIVE');
1179                             fnd_message.set_token('PERSON_NUMBER', l_person_number);
1180                             fnd_message.set_token('COURSE', p_course_cd);
1181                             fnd_file.put_line(fnd_file.log, fnd_message.get);
1182                          ELSIF l_mode = '63' OR l_mode = '64' THEN
1183                              p_include:= 'N';
1184                             fnd_message.set_name('IGS','IGS_HE_MODE_VALID_FAILED');
1185                             fnd_message.set_token('PERSON_NUMBER', l_person_number);
1186                             fnd_message.set_token('COURSE', p_course_cd);
1187                             fnd_message.set_token('MODE', l_mode);
1188                             fnd_file.put_line(fnd_file.log, fnd_message.get);
1189                         END IF;
1190 
1191                      -- Check whether the field values satisfies the condition
1192                       IF  p_include = 'N' THEN
1193 
1194                          -- Student failed to satisfy the field validation
1195                           p_include := 'N';
1196                           p_qualified_teacher := 'N';
1197                           p_pt_study := 'N';
1198                       ELSE
1199                           -- Student satisfied the field validations  then return Y
1200                           p_include := 'Y';
1201                            -- Get the qualified_teacher column value
1202                           IF l_hesa_qual1 IN ('12','13','20') OR l_hesa_qual2 IN ('12','13','20') THEN
1203                              p_qualified_teacher := 'Y';
1204                           ELSE
1205                              p_qualified_teacher := 'N';
1206                           END IF;
1207                           -- get the PT_study column value
1208                           IF l_mode IN ('31','33','34','35','38','39','64') THEN
1209                              p_pt_study := 'Y';
1210                           ELSE
1211                              p_pt_study := 'N';
1212                           END IF;
1213                       END IF;
1214 
1215             -- for research students derive the field values
1216            ELSIF P_qual_type = 'R' THEN
1217 
1218 
1219                    -- Derive MSTUFEE (68) field value,
1220                    -- For Deriving MSTUFEE, required to pass special student (28), Mode of study (70) and Amount of tuituin fee (83) field values
1221                    -- Pass NULL to amount of tuition fee, this is not used while deriving MSTUFEE field value in the code
1222                    -- So first calculate Special student and MODE field values
1223                    --  MSTUFEE
1224                    --         |--- 28 (special student)
1225                    --         |--- 70 (Mode of study)
1226                    --         |--- 83 (Amt of tuition fee) Pass null, this value is not used to derive MSTUFEE field in get_maj_src_tu_fee
1227                    --
1228 
1229                        -- Derive Special Student (28) field value
1230                        l_oss_special_student := NULL;
1231                            l_hesa_special_student := NULL;
1232 
1233                        igs_he_extract_fields_pkg.get_special_student
1234                                   (p_ad_special_student   => l_he_ad_dtl.special_student_cd,
1235                                    p_spa_special_student  => l_spa.special_student,
1236                                    p_oss_special_student  => l_oss_special_student,
1237                                    p_hesa_special_student => l_hesa_special_student);
1238 
1239                         -- Calculate the MODE of study (70) value
1240                            l_mode := NULL;
1241                         igs_he_extract_fields_pkg.get_mode_of_study
1242                                   (p_person_id         =>  p_person_id,
1243                                    p_course_cd         =>  p_course_cd,
1244                                    p_version_number    =>  p_version_number,
1245                                    p_enrl_start_dt     =>  l_he_sub_header.enrolment_start_date,
1246                                    p_enrl_end_dt       =>  l_he_sub_header.enrolment_end_date,
1247                                    p_susa_study_mode   =>  l_yop_susa.study_mode,
1248                                    p_poous_study_mode  =>  l_he_poous.mode_of_study,
1249                                    p_attendance_type   =>  l_spa.attendance_type,
1250                                    p_mode_of_study     =>  l_mode);
1251 
1252                       -- Now calculate the major source of tuition fees (68) fieldvalue,
1253                  l_hesa_mstufee := NULL;
1254                       igs_he_extract_fields_pkg.get_maj_src_tu_fee
1255                                           (p_person_id         => p_person_id,
1256                                            p_enrl_start_dt     => l_he_sub_header.enrolment_start_date,
1257                                            p_enrl_end_dt       => l_he_sub_header.enrolment_end_date,
1258                                            p_special_stdnt     => l_hesa_special_student,
1259                                            p_study_mode        => l_mode,
1260                                            p_amt_tu_fee        => NULL,
1261                                            p_susa_mstufee      => l_yop_susa.student_fee,
1262                                            p_hesa_mstufee      => l_hesa_mstufee);
1263 
1264                              -- If field value is null or field value is not in the list then report the message in log file
1265                               IF l_hesa_mstufee IS NULL THEN
1266                                  p_include:= 'N';
1267                                  fnd_message.set_name('IGS','IGS_HE_MSTUFEE_FAIL_TO_DERIVE');
1268                                  fnd_message.set_token('PERSON_NUMBER', l_person_number);
1269                                  fnd_message.set_token('COURSE', p_course_cd);
1270                                  fnd_file.put_line(fnd_file.log, fnd_message.get);
1271                               ELSIF l_hesa_mstufee NOT IN ('11','12','13','14','15','16','17','19') THEN
1272                                  p_include:= 'N';
1273                                  fnd_message.set_name('IGS','IGS_HE_MSTUFEE_VALID_FAILED');
1274                                  fnd_message.set_token('PERSON_NUMBER', l_person_number);
1275                                  fnd_message.set_token('COURSE', p_course_cd);
1276                                  fnd_message.set_token('MSTUFEE', l_hesa_mstufee);
1277                                  fnd_file.put_line(fnd_file.log, fnd_message.get);
1278                               END IF;
1279 
1280                        -- Derive Reason for leaving institution (RSNLEAVE Field 33)
1281                           l_rsn_inst_left := NULL;
1282                        igs_he_extract_fields_pkg.get_rsn_inst_left
1283                                      (p_person_id        => P_person_id,
1284                                       p_course_cd        => p_course_cd,
1285                                       p_crs_req_comp_ind => l_spa.course_rqrmnt_complete_ind,
1286                                       p_crs_req_comp_dt  => l_spa.course_rqrmnts_complete_dt,
1287                                       p_disc_reason_cd   => l_spa.discontinuation_reason_cd,
1288                                       p_disc_dt          => l_spa.discontinued_dt,
1289                                       p_enrl_start_dt    => l_he_sub_header.enrolment_start_date,
1290                                       p_enrl_end_dt      => l_he_sub_header.enrolment_end_date,
1291                                       p_rsn_inst_left    => l_rsn_inst_left);
1292 
1293                             -- If field value is not in the list then report the message in log file
1294                             IF l_rsn_inst_left = '05' THEN
1295                                p_include:= 'N';
1296                                fnd_message.set_name('IGS','IGS_HE_RSNLEAVE_VALID_FAILED');
1297                                fnd_message.set_token('PERSON_NUMBER', l_person_number);
1298                                fnd_message.set_token('COURSE', p_course_cd);
1299                                fnd_message.set_token('RSNLEAVE', l_rsn_inst_left);
1300                                fnd_file.put_line(fnd_file.log, fnd_message.get);
1301                             END IF;
1302 
1303               -- Check whether the student satisfies the field validation
1304                       IF  p_include = 'N' THEN
1305                          -- Student failed to satisfy the field validation
1306                           p_include := 'N';
1307                           p_qualified_teacher := 'N';
1308                           p_pt_study := 'N';
1309                       ELSE
1310                           -- Student satisfied the field validations  then return Y
1311                           p_include := 'Y';
1312                           p_qualified_teacher := 'N';
1313                           p_pt_study := 'N';
1314                       END IF;
1315 
1316            END IF;  -- Qualifying period type
1317 
1318    EXCEPTION
1319      WHEN OTHERS THEN
1320         Fnd_Message.Set_Name('IGS','IGS_GE_UNHANDLED_EXP');
1321         Fnd_Message.Set_Token('NAME','igs_he_identify_target_pop.dlhe_review_spa');
1322         fnd_file.put_line(fnd_file.log, fnd_message.get);
1323         App_Exception.Raise_Exception;
1324 
1325    END dlhe_review_spa;
1326 
1327 END igs_he_identify_target_pop;