DBA Data[Home] [Help]

PACKAGE BODY: APPS.HRI_EDW_FCT_WRKFC_SPRTN

Source


1 PACKAGE BODY hri_edw_fct_wrkfc_sprtn AS
2 /* $Header: hriefwsp.pkb 115.7 2002/02/14 00:39:19 pkm ship       $ */
3   --
4   g_instance_fk        VARCHAR2(40);     -- Holds data source
5   --
6   /* Holds stage dates and reasons for each applicant */
7   g_success            NUMBER;
8   g_count NUMBER := 0;
9   --
10   -- Holds indicator showing whether invalid separation_mode is active
11   --
12   g_inv_sep_mode_on    VARCHAR2(200);
13   --
14   -- Set up globals for the PKS for gain, recruitment and na_edw as
15   -- these will not change during the session.
16   --
17   g_gain_type_pk       VARCHAR2(400); -- Holds gain type pk
18   g_recruitment_pk     VARCHAR2(400); -- Holds recruitment stage pk
19   --
20   -- The primary Key that is applied to any hierarchy that is not
21   -- relevant for the movement type.
22   --
23   g_na_edw_pk          VARCHAR2(140); -- Points to N/A row
24   --
25 /******************************************************************************/
26 /* This is a dummy function which calls the calc_abv function in the business */
27 /* process layer. It returns the assignment budget value of an applicant      */
28 /* given their assignment, the vacancy they are applying for, the effective   */
29 /* date the budget measurement type (BMT) and the applicant's business group  */
30 /******************************************************************************/
31 FUNCTION calc_abv(p_assignment_id     IN NUMBER,
32                   p_business_group_id IN NUMBER,
33                   p_budget_type       IN VARCHAR2,
34                   p_effective_date    IN DATE)
35                   RETURN NUMBER    IS
36 --
37   l_return_value   NUMBER := to_number(null);  -- Keeps the ABV to be returned
38 --
39 BEGIN
40 --
41   l_return_value := hri_bpl_abv.calc_abv
42         ( p_assignment_id      => p_assignment_id
43         , p_business_group_id  => p_business_group_id
44         , p_budget_type        => p_budget_type
45         , p_effective_date     => p_effective_date );
46 --
47 RETURN l_return_value;
48 --
49 EXCEPTION
50   WHEN OTHERS THEN
51     RETURN to_number(null);
52 END calc_abv;
53 --
54 --------------------------------------------------------------------------------
55 --  Procedure  : find_MOVEMENT_pk
56 --
57 --  Exceptions : NA
58 --
59 --  Description: Returns the PK of the separation or potential separation
60 --               in the Movement Type Dimension
61 --
62 --------------------------------------------------------------------------------
63 --
64 FUNCTION find_movement_fk(p_actual_termination_date    IN DATE
65                          ,p_accepted_termination_date  IN DATE
66                          ,p_notified_termination_date  IN DATE
67                          ,p_projected_termination_date IN DATE
68                          ,p_final_process_date         IN DATE
69                          ,p_reason                IN VARCHAR2
70                             )
71                    RETURN VARCHAR2 IS
72   --
73   l_return_string     VARCHAR2(800);    -- Keeps the string to return
74   l_stage_type        VARCHAR2(30);     -- Holds current stage
75   --
76   -- Movement Type PK is made by concatenating the following primary keys
77   --
78   l_loss_type_pk       VARCHAR2(400); -- Holds loss type pk
79   l_separation_pk      VARCHAR2(400); -- Holds separation stage pk
80   --
81   -- Numbers used to determine if involuntary separations are
82   -- being handled,  and if so whether the current Movement is
83   -- for an involuntary separation.
84   --
85   l_sep_rsn_type       VARCHAR2(30);
86   --
87   -- Describes the sort of loss that has been identified by
88   -- looking at the sep dates passed in.
89   --
90   l_loss_type          VARCHAR2(200);
91   l_loss_cat           VARCHAR2(200);
92   l_loss_rsn           VARCHAR2(200);
93   --
94   -- Cursor that queries a table that lists all involuntary
95   -- separation reasons.  This table also contains a flag
96   -- to indicate if involuntary separations are being detected
97   --
98   CURSOR c_sep_rsn_type IS
99   SELECT termination_type
100   FROM hri_inv_sprtn_rsns
101   WHERE reason = p_reason;
102   --
103 BEGIN
104   --
105 /* 115.5 - Look at final process first, then actual termination and so on */
106   IF (p_final_process_date IS NOT NULL) THEN
107     l_stage_type := 'FINAL';
108     l_loss_cat   := 'LOSSES';
109     l_loss_type  := 'LOSS_SEP';
110   ELSIF (p_actual_termination_date IS NOT NULL) THEN
111     l_stage_type := 'SEP';
112     l_loss_cat   := 'LOSSES';
113     l_loss_type  := 'LOSS_SEP';
114   ELSIF (p_projected_termination_date IS NOT NULL) THEN
115     l_stage_type := 'PLANNED';
116     l_loss_cat   := 'POT_LOSSES';
117     l_loss_type  := 'POT_SEP';
118   ELSIF (p_accepted_termination_date IS NOT NULL) THEN
119     l_stage_type := 'ACCEPT';
120     l_loss_cat   := 'POT_LOSSES';
121     l_loss_type  := 'POT_SEP';
122   ELSIF (p_notified_termination_date IS NOT NULL) THEN
123     l_stage_type := 'NOTIFY';
124     l_loss_cat   := 'POT_LOSSES';
125     l_loss_type  := 'POT_SEP';
126   ELSE
127   /* Is not a separation return NA_EDW */
128     l_return_string := 'NA_EDW';
129     RETURN l_return_string;
130   END IF;
131   --
132   -- Check whether the reason passed in is voluntary or involuntary.
133   --
134   OPEN c_sep_rsn_type;
135   FETCH c_sep_rsn_type INTO l_sep_rsn_type;
136   CLOSE c_sep_rsn_type;
137   --
138   -- Is this an involuntary separation
139   --
140   IF (l_sep_rsn_type = 'I') THEN
141     l_loss_rsn := 'SEP_INV';
142   ELSIF (l_sep_rsn_type = 'V') THEN
143     l_loss_rsn := 'SEP_VOL';
144   ELSE
145     l_loss_rsn := l_loss_type;
146   END IF;
147   --
148   l_loss_type_pk := l_loss_cat || '-' || g_instance_fk || '-' || l_loss_type
149       || '-' || g_instance_fk || '-' || l_loss_rsn || '-' || g_instance_fk;
150   --
151   -- Construct the Separation Component of the Movement Type PK
152   --
153   l_separation_pk := 'SEP_STAGE-' || g_instance_fk || '-' || l_stage_type || '-' ||
154                      g_instance_fk || '-' || l_stage_type || '-' || g_instance_fk;
155   --
156   -- Construct the return string including the gain, loss, recruitment,
157   -- and separation hierarchy PKs
158   --
159   l_return_string := g_gain_type_pk || '-' || l_loss_type_pk  || '-' ||
160                      g_recruitment_pk || '-' || l_separation_pk || '-'
161                      || g_instance_fk;
162   --
163   RETURN l_return_string;
164   --
165 END find_movement_fk;
166 --
167 PROCEDURE populate_sep_rsns
168 IS
169 
170   l_formula_id        NUMBER;
171   l_term_type         VARCHAR2(30);
172   l_termination_type  VARCHAR2(30);
173   l_update_allowed    VARCHAR2(30);
174 
175   CURSOR leaving_reasons_csr IS
176   SELECT lookup_code
177   FROM hr_lookups
178   WHERE lookup_type = 'LEAV_REAS';
179 
180   CURSOR update_value_csr
181   (v_reason_code    VARCHAR2)
182   IS
183   SELECT termination_type, update_allowed_flag
184   FROM hri_inv_sprtn_rsns
185   WHERE reason = v_reason_code;
186 
187 BEGIN
188 
189   FOR v_leaving_reason IN leaving_reasons_csr LOOP
190 
191     l_formula_id := hr_person_flex_logic.GetTermTypeFormula
192                       ( p_business_group_id => 0 );
193 
194     l_term_type  := HR_PERSON_FLEX_LOGIC.GetTermType
195                       ( p_term_formula_id => l_formula_id,
196                         p_leaving_reason  => v_leaving_reason.lookup_code,
197                         p_session_date    => SYSDATE );
198 
199     OPEN update_value_csr(v_leaving_reason.lookup_code);
200     FETCH update_value_csr INTO l_termination_type, l_update_allowed;
201 
202   /* If value does not already exist */
203     IF (update_value_csr%NOTFOUND OR update_value_csr%NOTFOUND IS NULL) THEN
204       CLOSE update_value_csr;
205     /* Insert it */
206       INSERT INTO hri_inv_sprtn_rsns
207       ( reason
208       , termination_type
209       , update_allowed_flag )
210       VALUES
211         ( v_leaving_reason.lookup_code
212         , l_term_type
213         , 'N' );
214   /* If termination type has changed and reason is updateable */
215     ELSIF (l_update_allowed = 'Y' AND l_term_type <> l_termination_type) THEN
216       CLOSE update_value_csr;
217     /* Update the reason and reset the update allowed flag */
218       UPDATE hri_inv_sprtn_rsns
219       SET termination_type = l_term_type,
220           update_allowed_flag = 'N'
221       WHERE reason = v_leaving_reason.lookup_code;
222     ELSE
223       CLOSE update_value_csr;
224     END IF;
225 
226   END LOOP;
227 
228 END populate_sep_rsns;
229 
230 PROCEDURE set_update_flag( p_reason_code     IN VARCHAR2 := NULL,
231                            p_update_allowed  IN VARCHAR2)
232 IS
233 
234 BEGIN
235 
236 /* Check valid input */
240     UPDATE hri_inv_sprtn_rsns
237   IF (p_update_allowed = 'Y' OR p_update_allowed = 'N') THEN
238 
239   /* Update table */
241     SET update_allowed_flag = p_update_allowed
242     WHERE (reason = p_reason_code
243       OR p_reason_code IS NULL);
244 
245   END IF;
246 
247 END set_update_flag;
248 --
249 --------------------------------------------------------------------------------
250 --  Procedure  : populate_hri_prd_of_srvce
251 --
252 --  Exceptions : NA
253 --
254 --  Description: This procedure populates a table used by the
255 --               Separations Fact LCV to determine whether an assignment is
256 --               primary or not at each stage in the recruitment process
257 --
258 --------------------------------------------------------------------------------
259 --
260 PROCEDURE populate_hri_prd_of_srvce IS
261 
262 BEGIN
263 
264 /* Update reporting dates for separation stages for rows */
265 /* already existing in the performance table */
266   UPDATE hri_edw_period_of_service hps
267   SET
268   (past_notified_date
269   ,past_accepted_date
270   ,effective_projected_date
271   ,past_actual_date
272   ,past_final_date) =
273    (SELECT
274      DECODE(SIGN(pos.notified_termination_date - sysdate),
275               1, to_date(null),
276             pos.notified_termination_date)
277     ,DECODE(SIGN(pos.accepted_termination_date - sysdate),
278               1, to_date(null),
279             pos.accepted_termination_date)
280     ,NVL(pos.projected_termination_date, pos.actual_termination_date)
281     ,DECODE(SIGN(pos.actual_termination_date - sysdate),
282               1, to_date(null),
283             pos.actual_termination_date)
284     ,DECODE(SIGN(pos.final_process_date - sysdate),
285               1, to_date(null),
286             pos.final_process_date)
287     FROM per_periods_of_service   pos
288     WHERE hps.period_of_service_id = pos.period_of_service_id);
289 
290 -- This insert should pick up all assignment/person/period of
291 -- service combinations that do not exist in the performance
292 -- table hri_edw_period_of_service
293   INSERT INTO hri_edw_period_of_service
294     (assignment_id
295     ,person_id
296     ,period_of_service_id
297     ,past_notified_date
298     ,past_accepted_date
299     ,effective_projected_date
300     ,past_actual_date
301     ,past_final_date)
302   SELECT
303    asg.assignment_id
304   ,asg.person_id
305   ,pps.period_of_service_id
306   ,DECODE(SIGN(pps.notified_termination_date - sysdate),
307             1, to_date(null),
308           pps.notified_termination_date)
309   ,DECODE(SIGN(pps.accepted_termination_date - sysdate),
310             1, to_date(null),
311           pps.accepted_termination_date)
312   ,NVL(pps.projected_termination_date, pps.actual_termination_date)
313   ,DECODE(SIGN(pps.actual_termination_date - sysdate),
314             1, to_date(null),
315           pps.actual_termination_date)
316   ,DECODE(SIGN(pps.final_process_date - sysdate),
317             1, to_date(null),
318           pps.final_process_date)
319   FROM
320    per_all_assignments_f      asg
321   ,per_periods_of_service     pps
322   WHERE asg.person_id = pps.person_id
323   AND asg.period_of_service_id  = pps.period_of_service_id
324   AND asg.effective_start_date =
325      (SELECT MAX(asg2.effective_start_date)
326       FROM per_all_assignments_f asg2
327       WHERE asg2.assignment_id = asg.assignment_id)
328   AND NOT EXISTS (SELECT null
329                   FROM hri_edw_period_of_service hps
330                   WHERE hps.period_of_service_id = pps.period_of_service_id
331                   AND   hps.assignment_id        = asg.assignment_id);
332 
333 -- This update should pick up all the latest (date track) primary
334 -- primary assignment status for the point of notification
335 -- for each combination of assignment/person/period of service
336 -- that exist in the table hri_edw_period_of_service
337   UPDATE hri_edw_period_of_service hps
338   SET notified_trmntn_primary_flag =
339             (SELECT asg.primary_flag
340              FROM per_all_assignments_f   asg
341              WHERE hps.past_notified_date IS NOT NULL
342              AND hps.assignment_id = asg.assignment_id
343              AND hps.past_notified_date
344                BETWEEN asg.effective_start_date AND asg.effective_end_date);
345 
346 -- This update should pick up all the latest (date track) primary
347 -- primary assignment status for the point of acceptance
348 -- for each combination of assignment/person/period of service
349 -- that exist in the table hri_edw_period_of_service
350   UPDATE hri_edw_period_of_service hps
351   SET accepted_trmntn_primary_flag =
352             (SELECT asg.primary_flag
353              FROM per_all_assignments_f      asg
354              WHERE hps.past_accepted_date IS NOT NULL
355              AND hps.assignment_id = asg.assignment_id
356              AND hps.past_accepted_date
357                BETWEEN asg.effective_start_date AND asg.effective_end_date);
358 
359 -- This update should pick up all the latest (date track) primary
360 -- primary assignment status for the point of planned separation
361 -- for each combination of assignment/person/period of service
362 -- that exist in the table hri_edw_period_of_service
363   UPDATE hri_edw_period_of_service hps
364   SET projected_trmntn_primary_flag =
365     (SELECT asg.primary_flag
366      FROM per_all_assignments_f      asg
367      WHERE hps.effective_projected_date IS NOT NULL
368      AND hps.assignment_id = asg.assignment_id
369      AND LEAST(hps.effective_projected_date, SYSDATE)
370        BETWEEN asg.effective_start_date AND asg.effective_end_date);
371 
372 -- This update should pick up all the latest (date track) primary
376   UPDATE hri_edw_period_of_service hps
373 -- primary assignment status for the point of actual separation
374 -- for each combination of assignment/person/period of service
375 -- that exist in the table hri_edw_period_of_service
377   SET actual_trmntn_primary_flag =
378             (SELECT asg.primary_flag
379              FROM per_all_assignments_f      asg
380              WHERE hps.past_actual_date IS NOT NULL
381              AND hps.assignment_id = asg.assignment_id
382              AND hps.past_actual_date
383                BETWEEN asg.effective_start_date AND asg.effective_end_date);
384 
385 -- This update should pick up all the latest (date track) primary
386 -- primary assignment status for the point of final processing
387 -- for each combination of assignment/person/period of service
388 -- that exist in the table hri_edw_period_of_service
389   UPDATE hri_edw_period_of_service hps
390   SET final_process_primary_flag =
391              (SELECT asg.primary_flag
392               FROM per_all_assignments_f      asg
393               WHERE hps.past_final_date IS NOT NULL
394               AND hps.assignment_id = asg.assignment_id
395               AND hps.past_final_date
396                 BETWEEN asg.effective_start_date AND asg.effective_end_date);
397 
398 -- This update should pick up all the latest (date track) primary
399 -- primary assignment status for the point of the latest stage in
400 -- the recruitment process, for each combination of assignment/
401 -- person/period of service that exist in the table
402 -- hri_edw_period_of_service
403   UPDATE hri_edw_period_of_service hps
404   SET latest_stage_primary_flag =
405     (SELECT asg.primary_flag
406      FROM per_all_assignments_f   asg
407      WHERE hps.assignment_id = asg.assignment_id
408      AND NVL(hps.past_final_date,
409            NVL(hps.past_actual_date,
410              NVL(hps.effective_projected_date,
411                NVL(hps.past_accepted_date,
412                  NVL(hps.past_notified_date,sysdate)))))
413           BETWEEN asg.effective_start_date AND asg.effective_end_date);
414   --
415 END populate_hri_prd_of_srvce;
416 --
417 BEGIN
418   --
419   -- Get instance code
420   --
421   SELECT instance_code INTO g_instance_fk
422   FROM edw_local_instance;
423   --
424   --  Set Globals up used multiple times later
425   --
426   --  Construct the default NA_EDW pk for any of the Movement
427   --  Type hierarchies.
428   --
429   g_na_edw_pk := 'NA_EDW-' || g_instance_fk || '-NA_EDW-' ||
430                g_instance_fk || '-NA_EDW-' || g_instance_fk;
431   g_recruitment_pk := g_na_edw_pk;
432   g_gain_type_pk   := g_na_edw_pk;
433   --
434 END hri_edw_fct_wrkfc_sprtn;