DBA Data[Home] [Help]

APPS.HRI_EDW_FCT_WRKFC_SPRTN SQL Statements

The following lines contain the word 'select', 'insert', 'update' or 'delete':

Line: 99

  SELECT termination_type
  FROM hri_inv_sprtn_rsns
  WHERE reason = p_reason;
Line: 173

  l_update_allowed    VARCHAR2(30);
Line: 176

  SELECT lookup_code
  FROM hr_lookups
  WHERE lookup_type = 'LEAV_REAS';
Line: 180

  CURSOR update_value_csr
  (v_reason_code    VARCHAR2)
  IS
  SELECT termination_type, update_allowed_flag
  FROM hri_inv_sprtn_rsns
  WHERE reason = v_reason_code;
Line: 199

    OPEN update_value_csr(v_leaving_reason.lookup_code);
Line: 200

    FETCH update_value_csr INTO l_termination_type, l_update_allowed;
Line: 203

    IF (update_value_csr%NOTFOUND OR update_value_csr%NOTFOUND IS NULL) THEN
      CLOSE update_value_csr;
Line: 205

    /* Insert it */
      INSERT INTO hri_inv_sprtn_rsns
      ( reason
      , termination_type
      , update_allowed_flag )
      VALUES
        ( v_leaving_reason.lookup_code
        , l_term_type
        , 'N' );
Line: 214

  /* If termination type has changed and reason is updateable */
    ELSIF (l_update_allowed = 'Y' AND l_term_type <> l_termination_type) THEN
      CLOSE update_value_csr;
Line: 217

    /* Update the reason and reset the update allowed flag */
      UPDATE hri_inv_sprtn_rsns
      SET termination_type = l_term_type,
          update_allowed_flag = 'N'
      WHERE reason = v_leaving_reason.lookup_code;
Line: 223

      CLOSE update_value_csr;
Line: 230

PROCEDURE set_update_flag( p_reason_code     IN VARCHAR2 := NULL,
                           p_update_allowed  IN VARCHAR2)
IS

BEGIN

/* Check valid input */
  IF (p_update_allowed = 'Y' OR p_update_allowed = 'N') THEN

  /* Update table */
    UPDATE hri_inv_sprtn_rsns
    SET update_allowed_flag = p_update_allowed
    WHERE (reason = p_reason_code
      OR p_reason_code IS NULL);
Line: 247

END set_update_flag;
Line: 264

/* Update reporting dates for separation stages for rows */
/* already existing in the performance table */
  UPDATE hri_edw_period_of_service hps
  SET
  (past_notified_date
  ,past_accepted_date
  ,effective_projected_date
  ,past_actual_date
  ,past_final_date) =
   (SELECT
     DECODE(SIGN(pos.notified_termination_date - sysdate),
              1, to_date(null),
            pos.notified_termination_date)
    ,DECODE(SIGN(pos.accepted_termination_date - sysdate),
              1, to_date(null),
            pos.accepted_termination_date)
    ,NVL(pos.projected_termination_date, pos.actual_termination_date)
    ,DECODE(SIGN(pos.actual_termination_date - sysdate),
              1, to_date(null),
            pos.actual_termination_date)
    ,DECODE(SIGN(pos.final_process_date - sysdate),
              1, to_date(null),
            pos.final_process_date)
    FROM per_periods_of_service   pos
    WHERE hps.period_of_service_id = pos.period_of_service_id);
Line: 293

  INSERT INTO hri_edw_period_of_service
    (assignment_id
    ,person_id
    ,period_of_service_id
    ,past_notified_date
    ,past_accepted_date
    ,effective_projected_date
    ,past_actual_date
    ,past_final_date)
  SELECT
   asg.assignment_id
  ,asg.person_id
  ,pps.period_of_service_id
  ,DECODE(SIGN(pps.notified_termination_date - sysdate),
            1, to_date(null),
          pps.notified_termination_date)
  ,DECODE(SIGN(pps.accepted_termination_date - sysdate),
            1, to_date(null),
          pps.accepted_termination_date)
  ,NVL(pps.projected_termination_date, pps.actual_termination_date)
  ,DECODE(SIGN(pps.actual_termination_date - sysdate),
            1, to_date(null),
          pps.actual_termination_date)
  ,DECODE(SIGN(pps.final_process_date - sysdate),
            1, to_date(null),
          pps.final_process_date)
  FROM
   per_all_assignments_f      asg
  ,per_periods_of_service     pps
  WHERE asg.person_id = pps.person_id
  AND asg.period_of_service_id  = pps.period_of_service_id
  AND asg.effective_start_date =
     (SELECT MAX(asg2.effective_start_date)
      FROM per_all_assignments_f asg2
      WHERE asg2.assignment_id = asg.assignment_id)
  AND NOT EXISTS (SELECT null
                  FROM hri_edw_period_of_service hps
                  WHERE hps.period_of_service_id = pps.period_of_service_id
                  AND   hps.assignment_id        = asg.assignment_id);
Line: 337

  UPDATE hri_edw_period_of_service hps
  SET notified_trmntn_primary_flag =
            (SELECT asg.primary_flag
             FROM per_all_assignments_f   asg
             WHERE hps.past_notified_date IS NOT NULL
             AND hps.assignment_id = asg.assignment_id
             AND hps.past_notified_date
               BETWEEN asg.effective_start_date AND asg.effective_end_date);
Line: 350

  UPDATE hri_edw_period_of_service hps
  SET accepted_trmntn_primary_flag =
            (SELECT asg.primary_flag
             FROM per_all_assignments_f      asg
             WHERE hps.past_accepted_date IS NOT NULL
             AND hps.assignment_id = asg.assignment_id
             AND hps.past_accepted_date
               BETWEEN asg.effective_start_date AND asg.effective_end_date);
Line: 363

  UPDATE hri_edw_period_of_service hps
  SET projected_trmntn_primary_flag =
    (SELECT asg.primary_flag
     FROM per_all_assignments_f      asg
     WHERE hps.effective_projected_date IS NOT NULL
     AND hps.assignment_id = asg.assignment_id
     AND LEAST(hps.effective_projected_date, SYSDATE)
       BETWEEN asg.effective_start_date AND asg.effective_end_date);
Line: 376

  UPDATE hri_edw_period_of_service hps
  SET actual_trmntn_primary_flag =
            (SELECT asg.primary_flag
             FROM per_all_assignments_f      asg
             WHERE hps.past_actual_date IS NOT NULL
             AND hps.assignment_id = asg.assignment_id
             AND hps.past_actual_date
               BETWEEN asg.effective_start_date AND asg.effective_end_date);
Line: 389

  UPDATE hri_edw_period_of_service hps
  SET final_process_primary_flag =
             (SELECT asg.primary_flag
              FROM per_all_assignments_f      asg
              WHERE hps.past_final_date IS NOT NULL
              AND hps.assignment_id = asg.assignment_id
              AND hps.past_final_date
                BETWEEN asg.effective_start_date AND asg.effective_end_date);
Line: 403

  UPDATE hri_edw_period_of_service hps
  SET latest_stage_primary_flag =
    (SELECT asg.primary_flag
     FROM per_all_assignments_f   asg
     WHERE hps.assignment_id = asg.assignment_id
     AND NVL(hps.past_final_date,
           NVL(hps.past_actual_date,
             NVL(hps.effective_projected_date,
               NVL(hps.past_accepted_date,
                 NVL(hps.past_notified_date,sysdate)))))
          BETWEEN asg.effective_start_date AND asg.effective_end_date);
Line: 421

  SELECT instance_code INTO g_instance_fk
  FROM edw_local_instance;