DBA Data[Home] [Help]

PACKAGE BODY: APPS.BEN_PREM_PRTT_CREDITS_MO

Source


1 package body ben_prem_prtt_credits_mo as
2 /* $Header: benprprc.pkb 120.0 2005/05/28 09:20:54 appldev noship $ */
3 g_package             varchar2(80) := 'ben_prem_prtt_credits_mo';
4 -- ----------------------------------------------------------------------------
5 -- |------------------------------< main >------------------------------------|
6 -- ----------------------------------------------------------------------------
7 -- This is the procedure to call to determine all participant premium credits
8 -- for prior months.
9 procedure main
10   (p_validate                 in varchar2 default 'N',
11    p_person_id                in number default null,
12    p_pl_id                    in number default null,
13    p_person_selection_rule_id in number default null,
14    p_comp_selection_rule_id   in number default null,
15    p_pgm_id                   in number default null,
16    p_pl_typ_id                in number default null,
17    p_organization_id          in number default null,
18    p_legal_entity_id          in number default null,
19    p_business_group_id        in number,
20    p_mo_num                   in number,
21    p_yr_num                   in number,
22    p_first_day_of_month       in date,
23    p_effective_date           in date) is
24     --
25   l_package               varchar2(80) := g_package||'.main';
26   l_error_text            varchar2(200) := null;
27   --
28   -- participants that have paid a premium for coverage that ended and
29   -- credit look-backs are defined for that actual-premium.  This cursor will
30   -- really limit the results that are processed in this run.
31   --
32   cursor c_results is
33     select distinct pen.prtt_enrt_rslt_id, pen.enrt_cvg_thru_dt, pen.pgm_id,
34            pen.pl_id, pen.oipl_id, pen.person_id, pen.ler_id, pen.pl_typ_id,
35            pen.prtt_enrt_rslt_stat_cd, pen.sspndd_flag, pil.per_in_ler_stat_cd,
36            pen.effective_start_date, pen.effective_end_date,
37            pen.enrt_cvg_strt_dt
38     from   ben_prtt_enrt_rslt_f pen, ben_prtt_prem_f ppe,
39            ben_per_in_ler pil
40            ,ben_prtt_prem_by_mo_f prm, ben_actl_prem_f apr
41     where
42          ( (pen.sspndd_flag = 'N'
43            -- Credits for 'normal' stuff and
44            -- Task 417:  Credits for:
45            -- c. voided results (RETRO and PRO).
46     and    (pen.prtt_enrt_rslt_stat_cd is null
47            or pen.prtt_enrt_rslt_stat_cd = 'VOIDD')
48            -- result effective START date is this month
49    -- and    pen.effective_start_date between
50    --        p_first_day_of_month and p_effective_date
51            -- cvg ended prior to the end of this month - needed for prospective
52            -- for retro we really care about cvg ending last month.
53     and    pen.enrt_cvg_thru_dt between  add_months(p_effective_date, - (apr.cr_lkbk_val))
54                     and p_effective_date
55            -- a premium was paid for the month in which coverage ended
56     and    ((prm.mo_num = to_char(pen.enrt_cvg_thru_dt,'mm')
57            and    prm.yr_num = to_char(pen.enrt_cvg_thru_dt,'yyyy'))
58            -- or a premium was paid for the month after cvg ended
59            or    (prm.mo_num = to_char(add_months(pen.enrt_cvg_thru_dt,1),'mm')
60            and    prm.yr_num = to_char(add_months(pen.enrt_cvg_thru_dt,1),'yyyy')))
61     and    pil.per_in_ler_stat_cd not in ('BCKDT')
62     and    p_effective_date between
63            ppe.effective_start_date and ppe.effective_end_date
64     and    p_effective_date between
65            prm.effective_start_date and prm.effective_end_date)
66     -- Task 415:  Credits for:
67     -- b. suspended results (PRO).
68     or     (pen.sspndd_flag = 'Y'
69     and    pen.prtt_enrt_rslt_stat_cd is null
70            -- result effective START date is this month
71     and    pen.effective_start_date between
72            p_first_day_of_month and p_effective_date
73            -- this will only happen for prospective, this is redundant
74     and    apr.prsptv_r_rtsptv_cd = 'PRO'
75            -- a premium was paid for the month in which coverage was suspended
76     and    ((prm.mo_num = to_char(p_effective_date,'mm')
77            and    prm.yr_num = to_char(p_effective_date,'yyyy')))
78     and    pil.per_in_ler_stat_cd not in ('VOIDD','BCKDT')
79     and    p_effective_date between
80            ppe.effective_start_date and ppe.effective_end_date
81     and    p_effective_date between
82            prm.effective_start_date and prm.effective_end_date)
83     -- Task 415: create prem credits for:
84     -- INTERIM dt-ended before cvg started criteria (PRO):
85     or    (pen.prtt_enrt_rslt_stat_cd is null
86            -- rows where result was ended, not just date-track updated.
87     and    pen.object_version_number = (select max(object_version_number)
88            from ben_prtt_enrt_rslt_f p where p.prtt_enrt_rslt_id = pen.prtt_enrt_rslt_id)
89            -- cvg started sometime this month - a pro prem could have been written
90     and    pen.enrt_cvg_strt_dt between p_first_day_of_month and p_effective_date
91            -- result effective END date is this month
92     and    pen.effective_end_date between
93            p_first_day_of_month and p_effective_date
94            -- date track ended before cvg started.
95     and    pen.effective_end_date < pen.enrt_cvg_strt_dt
96            -- a premium was paid for this month
97     and    (prm.mo_num = to_char(p_first_day_of_month,'mm')
98            and    prm.yr_num = to_char(p_first_day_of_month,'yyyy'))
99            -- this will only happen for prospective, this is redundant
100     and    apr.prsptv_r_rtsptv_cd = 'PRO'
101     and    pil.per_in_ler_stat_cd not in ('VOIDD','BCKDT'))
102     -- Task 417: create prem credits for:
103     -- BACKED OUT per in ler criteria (RETRO AND PRO):
104     -- when the premium processfor backedout le
105     -- get all the prem_by_mo for the period between the process and lkbk  prd
106     -- then find ler_id for the premium is backed out and make sure credit entries are not alread ycreated for the
107     --  premium bug 3692290
108     or (pil.per_in_ler_stat_cd in ( 'BCKDT' ,'VOIDD')
109        --- and    pil.bckt_dt between
110        ---        p_first_day_of_month and p_effective_date
111        --- and    p_effective_date between
112        ---        ppe.effective_start_date and ppe.effective_end_date
113        --- and    p_effective_date between
114        ---        prm.effective_start_date and prm.effective_end_date
115          and pil.per_in_ler_id = ppe.per_in_ler_id
116          and ppe.prtt_prem_id  = prm.prtt_prem_id
117          and prm.cr_val is null
118          and prm.effective_start_date between add_months(p_effective_date, - (apr.cr_lkbk_val))
119                and p_effective_date
120           and  p_effective_date  between
121                ppe.effective_start_date and ppe.effective_end_date
122           and  p_effective_date  between
123                prm.effective_start_date and prm.effective_end_date
124           and not exists
125             ( select pmo.prtt_prem_by_mo_id from  ben_prtt_prem_by_mo_f pmo
126               where  pmo.prtt_prem_by_mo_id = prm.prtt_prem_by_mo_id
127               and    pmo.cr_val is not null
128             )
129        )
130     )
131     and    pen.comp_lvl_cd not in ('PLANFC', 'PLANIMP')  -- not a dummy plan
132     and    (pen.pl_id = p_pl_id  or p_pl_id is null)
133     and    (pen.pl_typ_id = p_pl_typ_id or p_pl_typ_id is null)
134     and    (pen.pgm_id = p_pgm_id or p_pgm_id is null)
135     and    (pen.person_id = p_person_id or p_person_id is null)
136            -- premium was not already credited
137     and    nvl(prm.cr_val,0) = 0
138            -- credit look backs defined
139     and    apr.cr_lkbk_val is not null
140     and    apr.cr_lkbk_val <>0  -- bug 1213601
141     and    pen.business_group_id = p_business_group_id
142     and    pen.prtt_enrt_rslt_id = ppe.prtt_enrt_rslt_id
143     and    ppe.prtt_prem_id = prm.prtt_prem_id
144     and    ppe.actl_prem_id = apr.actl_prem_id
145     and    apr.prem_asnmt_cd = 'ENRT'
146     and    p_effective_date between
147            apr.effective_start_date and apr.effective_end_date
148     -- Do not use effective date against ppe nor prm because we want to pick
149     -- up interim rows that were end dated.
150     --and    p_effective_date between
151     --       ppe.effective_start_date and ppe.effective_end_date
152     --and    p_effective_date between
153     --       prm.effective_start_date and prm.effective_end_date
154     and    pil.per_in_ler_id=ppe.per_in_ler_id
155     and    pil.business_group_id=ppe.business_group_id;
156 
157   l_results c_results%rowtype;
158 
159   -- Participant Premiums to be processed:
160   cursor c_prems (p_prtt_enrt_rslt_id number
161                  ,p_interim varchar2) is
162     select apr.actl_prem_id, apr.prtl_mo_det_mthd_cd, apr.prtl_mo_det_mthd_rl,
163            apr.cr_lkbk_crnt_py_only_flag, apr.cr_lkbk_uom,
164            apr.cr_lkbk_val, ppe.prtt_prem_id, apr.wsh_rl_dy_mo_num,
165            apr.rndg_cd, apr.rndg_rl, ppe.std_prem_val, apr.prsptv_r_rtsptv_cd,
166            apr.lwr_lmt_calc_rl, apr.lwr_lmt_val,
167            apr.upr_lmt_calc_rl, apr.upr_lmt_val
168     from   ben_actl_prem_f apr, ben_prtt_prem_f ppe
169     where  apr.prem_asnmt_cd = 'ENRT'
170     and    apr.cr_lkbk_val is not null   -- bug 1213601
171     and    apr.cr_lkbk_val <>0
172     and    ppe.prtt_enrt_rslt_id = p_prtt_enrt_rslt_id
173     and    ppe.actl_prem_id = apr.actl_prem_id
174     and    apr.business_group_id+0 = p_business_group_id
175     and    (p_interim = 'Y'
176      or    p_effective_date between
177            ppe.effective_start_date and ppe.effective_end_date)
178     and    p_effective_date between
179            apr.effective_start_date and apr.effective_end_date;
180   -- l_prems c_prems%rowtype;
181 
182   -- participant prem by month row:
183   cursor c_prem_by_mo (p_prtt_prem_id number
184                ,p_process_mo_num number
185                ,p_process_yr_num number
186                ,p_interim varchar2 ) is
187     select prm.val, prm.prtt_prem_by_mo_id, prm.mo_num, prm.yr_num,
188            prm.object_version_number, prm.effective_start_date
189     from   ben_prtt_prem_by_mo_f prm
190     where  prm.prtt_prem_id = p_prtt_prem_id
191     and    prm.mo_num = p_process_mo_num
192     and    prm.yr_num = p_process_yr_num
193     and    prm.business_group_id+0 = p_business_group_id
194     and    (p_interim = 'Y'
195      or    p_effective_date between
196            prm.effective_start_date and prm.effective_end_date);
197   l_prem_by_mo c_prem_by_mo%rowtype;
198 
199   -- plan year period for the effective date and the plan:
200   cursor c_pl_yr  (p_pgm_id number, p_pl_id number) is
201     select yrp.start_date
202     from   ben_yr_perd yrp, ben_popl_yr_perd cpy
203     where  yrp.business_group_id+0 = p_business_group_id
204     and    p_effective_date between
205            yrp.start_date and yrp.end_date
206     and    yrp.yr_perd_id = cpy.yr_perd_id
207     and    ((cpy.pgm_id = p_pgm_id) or
208            (p_pgm_id is null and cpy.pl_id = p_pl_id));
209   l_pl_yr c_pl_yr%rowtype;
210 
211   cursor c_opt(l_oipl_id  number) is
212 	select opt_id from ben_oipl_f oipl
213 	where oipl.oipl_id = l_oipl_id
214         and p_effective_date between
215             oipl.effective_start_date and oipl.effective_end_date;
216   l_opt c_opt%rowtype;
217 
218   l_effective_start_date date;
219   l_effective_end_date   date;
220   l_ovn                  number;
221   l_process_date         date;
222   l_process_mo_num       number;
223   l_process_yr_num       number;
224   l_cvg_end_day_num      number;
225   l_earliest_date        date;
226   l_cvg_end_mo           varchar2(1);
227   l_val                  number;
228   l_datetrack_mode       varchar2(30);
229   l_rule_ret             char(1);
230   l_interim              varchar2(1);
231   l_effective_date       date;
232   l_prem_val             number;
233 
234 begin
235   hr_utility.set_location ('Entering '||l_package,10);
236   savepoint process_premium_credits;
237   -- p_effective_date is always the last day of the month this is being run
238   -- loop thru results that may have a credit  required.
239   for l_results in c_results loop
240      hr_utility.set_location ('loop l_results '||
241                 to_char(l_results.prtt_enrt_rslt_id),12);
242 
243      l_rule_ret := 'Y';
244      if p_person_selection_rule_id is not null then
245         hr_utility.set_location('found a person rule',14);
246         l_rule_ret := ben_batch_utils.person_selection_rule
247                     (p_person_id               => l_results.person_id
248                     ,p_business_group_id       => p_business_group_id
249                     ,p_person_selection_rule_id=> p_person_selection_rule_id
250                     ,p_effective_date          => p_effective_date
251                     );
252      end if;
253      if l_rule_ret = 'Y'  then
254         if l_results.oipl_id is not null then
255            open c_opt(l_results.oipl_id);
256            fetch c_opt into l_opt;
257            close c_opt;
258         end if;
259      end if;
260 
261      if l_rule_ret = 'Y' and p_comp_selection_rule_id is not null then
262         hr_utility.set_location('found a comp object rule',16);
263         if l_results.oipl_id is not null then
264            open c_opt(l_results.oipl_id);
265            fetch c_opt into l_opt;
266            close c_opt;
267         end if;
268 
269         l_rule_ret:=ben_maintain_designee_elig.comp_selection_rule(
270                 p_person_id                => l_results.person_id
271                ,p_business_group_id        => p_business_group_id
272                ,p_pgm_id                   => l_results.pgm_id
273                ,p_pl_id                    => l_results.pl_id
274                ,p_pl_typ_id                => l_results.pl_typ_id
275                ,p_opt_id                   => l_opt.opt_id
276                ,p_oipl_id                  => l_results.oipl_id
277                ,p_ler_id                   => null  -- do not call with ler.
278                ,p_comp_selection_rule_id   => p_comp_selection_rule_id
279                ,p_effective_date           => p_effective_date
280       );
281      end if;
282 
283      -- rules say to continue with person and comp object
284      if l_rule_ret = 'Y' then
285 
286        -- day the coverage ended is needed for determining a partial month credit.
287        l_cvg_end_day_num :=  to_char(l_results.enrt_cvg_thru_dt,'DD');
288        if l_results.sspndd_flag = 'Y' then
289           -- if result is suspended, we need to 'end cvg' with the suspend date,
290           -- because there is no cvg end date set.
291           l_results.enrt_cvg_thru_dt := l_results.effective_start_date;
292        end if;
293        if l_results.enrt_cvg_strt_dt > l_results.effective_end_date then
294           -- we're dealing with an interim result ended before cvg started.
295           l_interim := 'Y';
296        else l_interim := 'N';
297        end if;
298 
299        -- loop thru the prtt_prems for the result
300        for l_prems in c_prems
301                     (p_prtt_enrt_rslt_id => l_results.prtt_enrt_rslt_id
302                     ,p_interim           => l_interim) loop
303           hr_utility.set_location ('loop prems '||to_char(l_prems.prtt_prem_id),14);
304 
305           if (l_prems.prsptv_r_rtsptv_cd = 'RETRO'
306              and l_results.enrt_cvg_thru_dt < p_first_day_of_month) or
307              l_prems.prsptv_r_rtsptv_cd = 'PRO' or
308              l_results.per_in_ler_stat_cd = 'BCKDT'  then
309 
310              -- For retro premiums, a credit is only calculated if the cvg
311              -- ended before the beginning of this month.  If cvg ended during
312              -- this month, the correct premium value would have been
313              -- calculated in benprprm.
314              -- For Prospective premiums, if cvg ended this month, we must
315              -- calc a credit, because benprprm deals with next month's
316              -- cvg for PRO premiums.
317              -- For Backed Out results, the cvg end date is not set, we want
318              -- to credit all premiums.
319 
320              -- actl-prem look-back converted into earliest date to provide premium credits
321              -- Lookback UOM should only ever be 'Month', but I'd already coded all
322              -- this, so  here it stays.
323              if l_prems.cr_lkbk_uom = 'DY' then
324                 l_earliest_date :=
325                   to_date('01-'||to_char(p_effective_date - l_prems.cr_lkbk_val,'MM-YYYY'),
326                   'DD-MM-YYYY');
327              elsif l_prems.cr_lkbk_uom = 'WK' then
331                   'DD-MM-YYYY');
328                 l_earliest_date :=
329                   to_date('01-'||
330                   to_char(p_effective_date - (l_prems.cr_lkbk_val*7),'MM-YYYY'),
332              elsif l_prems.cr_lkbk_uom = 'MO' then
333                 l_earliest_date :=
334                   to_date('01-'||
335                   to_char(add_months(p_effective_date , -l_prems.cr_lkbk_val),'MM-YYYY'),
336                   'DD-MM-YYYY');
337              else  --if l_prems.cr_lkbk_uom = 'YR' then
338                 l_earliest_date :=
339                   to_date('01-'||
340                   to_char(add_months(p_effective_date , -(l_prems.cr_lkbk_val*12)),'MM-YYYY'),
341                   'DD-MM-YYYY');
342              end if;
343 
344              if l_prems.cr_lkbk_crnt_py_only_flag = 'Y' then
345                  hr_utility.set_location ('py_only_flag = Y ',14);
346                  -- don't go before the current plan year.
347                  open c_pl_yr (p_pgm_id => l_results.pgm_id
348                               ,p_pl_id  => l_results.pl_id);
349                  fetch c_pl_yr into l_pl_yr;
350                  if c_pl_yr%found then
351                     if l_earliest_date < l_pl_yr.start_date then
352                        l_earliest_date :=
353                          to_date('01-'||to_char(l_pl_yr.start_date,'mm-yyyy'),'dd-mm-yyyy');
354                     end if;
355                  end if;
356                  close c_pl_yr;
357              end if;
358              hr_utility.set_location ('earliest date '||
359                      to_char(l_earliest_date,'dd-mon-yyyy'),17);
360 
361              -- for each premium we loop thru, load the earliest date we want to
362              -- process a credit for.
363              if l_results.per_in_ler_stat_cd = 'BCKDT' or
364                 l_interim = 'Y' then
365                 -- if result is backed out or we are end-dating a result before
366                 -- coverage starts, we need to start with the cvg strt dt,
367                 -- because there is no cvg end date set.
368                 l_process_date :=
369                  to_date('01-'||to_char(l_results.enrt_cvg_strt_dt,'MM-YYYY'),'DD-MM-YYYY');
370                 l_process_mo_num := to_char(l_results.enrt_cvg_strt_dt,'MM');
371                 l_process_yr_num := to_char(l_results.enrt_cvg_strt_dt,'YYYY');
372                 -- this flag is used to determine partial month.  in these cases, we
373                 -- do not want to calc partial month credit, we want to credit the
374                 -- entire prem amt.
375                 l_cvg_end_mo := 'N';
376              else
377                 -- Start with the coverage end date month.  use the first day of the month
378                 -- for comparison's sake.
379                 l_process_date :=
380                  to_date('01-'||to_char(l_results.enrt_cvg_thru_dt,'MM-YYYY'),'DD-MM-YYYY');
381                 l_process_mo_num := to_char(l_results.enrt_cvg_thru_dt,'MM');
382                 l_process_yr_num := to_char(l_results.enrt_cvg_thru_dt,'YYYY');
383                 l_cvg_end_mo := 'Y';
384              end if;
385 
386              loop
387                -- If month we are about to process is before the earliest month
388                -- we should process, then skip to next month.
389                hr_utility.set_location ('process date '||
390                         to_char(l_process_date,'dd-mon-yyyy'),20);
391                if l_process_date >= l_earliest_date and
392                   l_results.enrt_cvg_thru_dt <> last_day(l_process_date) then
393                  open c_prem_by_mo
394                        (p_prtt_prem_id   => l_prems.prtt_prem_id
395                        ,p_process_mo_num => l_process_mo_num
396                        ,p_process_yr_num => l_process_yr_num
397                        ,p_interim        => l_interim) ;
398                  fetch c_prem_by_mo into l_prem_by_mo;
399 
400                  -- l_val is what they paid for the month in question
401                  l_val := l_prem_by_mo.val;
402                  hr_utility.set_location ('prem amt '||to_char(l_val),24);
403                  if c_prem_by_mo%found then
404                  hr_utility.set_location ('prem amt ',26);
405                      -- this might be a partial credit for month where
406                      -- cvg ended, unless cvg ended on last day of month.
407                      -- Don't calc partial month for voided or backed out results,
408                      -- credit the entire premium amt.
409                      -- Also, do not calc partial credit if the cvg thru dt is less
410                      -- than the cvg strt dt (or rslt sspndd before cvg starts)
411                      -- even the coverage ended eof month and the partial calc code is rl or proration
412                      -- call the partial calcualtion
413                      if l_cvg_end_mo = 'Y'
414                         and ( ( l_results.enrt_cvg_thru_dt <> last_day(l_process_date)
415                                 and to_char(l_results.enrt_cvg_thru_dt, 'MM-RRRR') = to_char(l_process_date,'MM-RRRR')
416                               )
417                              or ( l_results.enrt_cvg_thru_dt =  last_day(l_process_date)
418                                   and l_prems.prtl_mo_det_mthd_cd in ('PRTVAL','WASHRULE','RL')
419                                 )
420                             )
421                         and l_results.prtt_enrt_rslt_stat_cd is null
422                         and l_results.enrt_cvg_strt_dt <= l_results.enrt_cvg_thru_dt then
423 
424                             hr_utility.set_location ('prem amt ',28);
428                           ,p_actl_prem_id        => l_prems.actl_prem_id
425                         ben_prem_prtt_monthly.compute_partial_mo
426                           (p_business_group_id   => p_business_group_id
427                           ,p_effective_date      => p_effective_date
429                           ,p_person_id           => l_results.person_id
430                           ,p_enrt_cvg_strt_dt    => null
431                           ,p_enrt_cvg_thru_dt    => l_results.enrt_cvg_thru_dt
432                           ,p_prtl_mo_det_mthd_cd => l_prems.prtl_mo_det_mthd_cd
433                           ,p_prtl_mo_det_mthd_rl => l_prems.prtl_mo_det_mthd_rl
434                           ,p_wsh_rl_dy_mo_num    => l_prems.wsh_rl_dy_mo_num
435                           ,p_rndg_cd             => l_prems.rndg_cd
436                           ,p_rndg_rl             => l_prems.rndg_rl
437                           ,p_lwr_lmt_calc_rl     => l_prems.lwr_lmt_calc_rl
438                           ,p_lwr_lmt_val         => l_prems.lwr_lmt_val
439                           ,p_upr_lmt_calc_rl     => l_prems.upr_lmt_calc_rl
440                           ,p_upr_lmt_val         => l_prems.upr_lmt_val
441                           ,p_pgm_id              => l_results.pgm_id
442                           ,p_pl_typ_id           => l_results.pl_typ_id
443                           ,p_pl_id               => l_results.pl_id
444                           ,p_opt_id              => l_opt.opt_id
445                           ,p_val                 => l_prems.std_prem_val);
446                         -- l_prems.std_prem_val when passed in was max premium he
447                         -- could have paid.  compute_partial returns what he should have
448                         -- paid.
449                         -- Convert this into a credit amount based on what he did pay.
450                         hr_utility.set_location ('debit  amt '||to_char(l_prem_by_mo.val),28);
451                         hr_utility.set_location ('partial   amt '||to_char(l_prems.std_prem_val),28);
452                         l_val := l_prem_by_mo.val - l_prems.std_prem_val;
453                      end if;
454                      hr_utility.set_location ('credit amt '||to_char(l_val),28);
455 
456                      if l_val > 0 then
457                        -- found a premium paid for this month, credit them.
458                        -- Do not write negative credits!
459                        if p_effective_date = l_prem_by_mo.effective_start_date then
460                           l_datetrack_mode := hr_api.g_correction;
461                        else
462                           l_datetrack_mode := hr_api.g_update;
463                        end if;
464                        if l_interim = 'Y' then
465                           -- if we are running with an ended interim, we can't update
466                           -- on the end-of-month date because the record was end-dated
467                           -- sometime this month.
468                           l_effective_date := l_results.effective_end_date;
469                           l_datetrack_mode := hr_api.g_correction;
470                        else
471                           l_effective_date := p_effective_date;
472                        end if;
473                        -- bug#2823935 -
474                        if l_datetrack_mode = hr_api.g_update then
475                            l_prem_val := null;
476                        else
477                            l_prem_val := l_prem_by_mo.val;
478                        end if;
479                        --
480                        ben_prtt_prem_by_mo_api.update_prtt_prem_by_mo
481                          (p_prtt_prem_by_mo_id    => l_prem_by_mo.prtt_prem_by_mo_id
482                          ,p_effective_start_date  => l_effective_start_date
483                          ,p_effective_end_date    => l_effective_end_date
484                          ,p_val                   => l_prem_val
485                          ,p_cr_val                => l_val
486                          ,p_object_version_number => l_prem_by_mo.object_version_number
487                          ,p_request_id            => fnd_global.conc_request_id
488                          ,p_program_application_id  => fnd_global.prog_appl_id
489                          ,p_program_id            => fnd_global.conc_program_id
490                          ,p_program_update_date   => sysdate
491                          ,p_effective_date        => l_effective_date
492                          ,p_datetrack_mode        => l_datetrack_mode);
493                        --
494                        -- write to the report table
495                        g_rec.rep_typ_cd            := 'PRCREDIT';
496                        g_rec.person_id             := l_results.person_id;
497                        g_rec.pgm_id                := l_results.pgm_id;
498                        g_rec.pl_id                 := l_results.pl_id;
499                        g_rec.oipl_id               := l_results.oipl_id;
500                        g_rec.pl_typ_id             := l_results.pl_typ_id;
501                        g_rec.actl_prem_id          := l_prems.actl_prem_id;
502                        g_rec.val                   := l_val;
503                        g_rec.mo_num                := l_process_mo_num;
504                        g_rec.yr_num                := l_process_yr_num;
505 
506                        benutils.write(p_rec => g_rec);
507 
508                      end if;
509                      close c_prem_by_mo;
510                  else
511                      close c_prem_by_mo;
512                      --exit;
513                  end if;   -- if c_prem_by_mo found
514                end if;
515                -- check following month until we run out of premiums paid
516                l_process_date := add_months(l_process_date,1);
517                if l_process_date > p_effective_date then
518                   exit ;
519                end if ;
520                l_process_mo_num := to_char(l_process_date,'MM');
521                l_process_yr_num := to_char(l_process_date,'YYYY');
522                l_cvg_end_mo := 'N';
523              end loop;
524           end if;  -- if 'pro' or ('retro' and cvg ended last month)
525        end loop;  -- prtt prems
526      end if;    -- rules pass
527   end loop;   -- results
528 
529   if p_validate = 'Y' then
530      Rollback to process_premium_credits;
531   end if;
532   hr_utility.set_location ('Leaving '||l_package,99);
533 exception
534   when others then
535     l_error_text := sqlerrm;
536     hr_utility.set_location ('Fail in '||l_package,999);
537     hr_utility.set_location ('with error '||l_error_text,999);
538     fnd_message.raise_error;
539 end main;
540 end ben_prem_prtt_credits_mo;