DBA Data[Home] [Help]

APPS.HRI_OPL_SUPH_HST_INC SQL Statements

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

Line: 49

/*               without the subordinate being updated                        */
/*             - Plus the initialization which is done by selecting all the   */
/*               top supervisors at the start of the collection               */
/*                                                                            */
/*     Processing the changes sequentially in reverse date order:             */
/*                                                                            */
/*    i) Calculate new chain for the person who has changed supervisor        */
/*   ii) Get the end date for the chain (held in global, or if not then the   */
/*       chain owner's termination date, or if not then end of time)          */
/*  iii) Insert new chain into hierarchy table                                */
/*   iv) Store the same information in a global data structure                */
/*    v) If the supervisor change is not the first record of the person then  */
/*       propagate the change down to all that person's subordinates making   */
/*       use of the data structure to avoid recalculating the same            */
/*       information twice                                                    */
/*                                                                            */
/*  3) Global structures are used to:                                         */
/*                                                                            */
/*    i) Bulk fetch the main loop                                             */
/*   ii) Bulk insert the chains into the hierarchy table                      */
/*  iii) Store information about the current chain being processed            */
/*   iv) Keep a note of which chains have been processed on a particular      */
/*       date to avoid re-processing the same information                     */
/*    v) Keep a note of the date each chain starts, so that the next time     */
/*       a chain is processed (on an earlier date) the end date is known      */
/*   vi) Store the terminated assignment status types so that it is quick to  */
/*       find out which are invalid at insert time                            */
/*  vii) Keep track of whether a supervisor is a leaf node                    */
/*                                                                            */
/*  4) Errors encountered which are specifically handled arise from data      */
/*     inconsistencies:                                                       */
/*                                                                            */
/*    i) Loops in supervisor chain - error is output to log file with the     */
/*       date and assignment in looped chain                                  */
/*   ii) Overlapping assignment records - these mean a unique constraint      */
/*       error is encountered when inserting. This is recovered and the       */
/*       offending row found. An error is recorded in the log and processing  */
/*       continues.                                                           */
/*                                                                            */
/******************************************************************************/

/* Information to be held for each link in a chain */
TYPE g_link_record_type IS RECORD
  (business_group_id       per_all_assignments_f.business_group_id%TYPE
  ,person_id               per_all_assignments_f.person_id%TYPE
  ,assignment_id           per_all_assignments_f.assignment_id%TYPE
  ,asg_status_id           per_all_assignments_f.assignment_status_type_id%TYPE
  ,invalid_flag            VARCHAR2(30)
  ,primary_asg_flag        per_all_assignments_f.primary_flag%TYPE
  ,leaf_node               VARCHAR2(30)
  ,end_date                per_all_assignments_f.effective_end_date%TYPE);
Line: 164

/* Inserts row into concurrent program log when the g_conc_request_flag has   */
/* been set to TRUE, otherwise does nothing                                   */
/******************************************************************************/
PROCEDURE output(p_text  VARCHAR2)
  IS

BEGIN

/* Write to the concurrent request log if called from a concurrent request */
  IF (g_conc_request_flag = TRUE) THEN

   /* Put text to log file */
     fnd_file.put_line(FND_FILE.log, p_text);
Line: 189

    SELECT ast.assignment_status_type_id
    FROM   per_assignment_status_types ast
    WHERE  ast.per_system_status = 'TERM_ASSIGN';
Line: 235

  SELECT /*+ index(ast PER_ASSIGNMENT_STATUS_TYPE_PK) use_nl(asg ast) */
   'N'
  FROM per_all_assignments_f  asg,
       per_assignment_status_types ast
  WHERE asg.supervisor_id = p_person_id
  AND asg.assignment_type = 'E'
  AND asg.primary_flag = 'Y'
  AND ast.assignment_status_type_id = asg.assignment_status_type_id
  AND ast.per_system_status <> 'TERM_ASSIGN'
  AND p_on_date BETWEEN asg.effective_start_date
                AND asg.effective_end_date;
Line: 261

/* Inserts row into global temporary table                                    */
/******************************************************************************/
PROCEDURE insert_row( p_sup_business_group_id   IN NUMBER
                    , p_sup_person_id           IN NUMBER
                    , p_sup_assignment_id       IN NUMBER
                    , p_sup_asg_status_id       IN NUMBER
                    , p_sup_level               IN NUMBER
                    , p_sup_inv_flag            IN VARCHAR2
                    , p_sub_business_group_id   IN NUMBER
                    , p_sub_person_id           IN NUMBER
                    , p_sub_assignment_id       IN NUMBER
                    , p_sub_asg_status_id       IN NUMBER
                    , p_sub_primary_asg_flag    IN VARCHAR2
                    , p_sub_level               IN NUMBER
                    , p_sub_relative_level      IN NUMBER
                    , p_sub_inv_flag            IN VARCHAR2
                    , p_effective_start_date    IN DATE
                    , p_effective_end_date      IN DATE
                    , p_orphan_flag             IN VARCHAR2
                    , p_sub_leaf_flag           IN VARCHAR2 ) IS

BEGIN

  BEGIN

    INSERT INTO hri_cs_suph
      (sup_business_group_id
      ,sup_person_id
      ,sup_assignment_id
      ,sup_assignment_status_type_id
      ,sup_level
      ,sup_invalid_flag_code
      ,sub_business_group_id
      ,sub_person_id
      ,sub_assignment_id
      ,sub_assignment_status_type_id
      ,sub_primary_asg_flag_code
      ,sub_level
      ,sub_relative_level
      ,sub_invalid_flag_code
      ,orphan_flag_code
      ,sub_leaf_flag_code
      ,effective_start_date
      ,effective_end_date)
        VALUES
              (p_sup_business_group_id
              ,p_sup_person_id
              ,p_sup_assignment_id
              ,p_sup_asg_status_id
              ,p_sup_level
              ,p_sup_inv_flag
              ,p_sub_business_group_id
              ,p_sub_person_id
              ,p_sub_assignment_id
              ,p_sub_asg_status_id
              ,p_sub_primary_asg_flag
              ,p_sub_level
              ,p_sub_relative_level
              ,p_sub_inv_flag
              ,p_orphan_flag
              ,p_sub_leaf_flag
              ,p_effective_start_date
              ,p_effective_end_date);
Line: 326

    output('Error inserting chain for:');
Line: 331

END insert_row;
Line: 334

/* Inserts chain from specified level                                         */
/******************************************************************************/
PROCEDURE insert_chain( p_level      IN NUMBER,
                        p_end_date   IN DATE) IS

BEGIN

  g_chain_transactions := g_chain_transactions + 1;
Line: 345

    insert_row
        (p_sup_business_group_id => g_crrnt_chain(i).business_group_id
        ,p_sup_person_id => g_crrnt_chain(i).person_id
        ,p_sup_assignment_id => g_crrnt_chain(i).assignment_id
        ,p_sup_asg_status_id => g_crrnt_chain(i).asg_status_id
        ,p_sup_level => i
        ,p_sup_inv_flag => g_crrnt_chain(i).invalid_flag
        ,p_sub_business_group_id  => g_crrnt_chain(p_level).business_group_id
        ,p_sub_person_id => g_crrnt_chain(p_level).person_id
        ,p_sub_assignment_id => g_crrnt_chain(p_level).assignment_id
        ,p_sub_asg_status_id => g_crrnt_chain(p_level).asg_status_id
        ,p_sub_primary_asg_flag => 'Y'
        ,p_sub_level => p_level
        ,p_sub_relative_level => p_level - i
        ,p_sub_inv_flag => g_crrnt_chain(p_level).invalid_flag
        ,p_effective_start_date => g_crrnt_chain_start_date
        ,p_effective_end_date => p_end_date
        ,p_orphan_flag => g_crrnt_chain_orphan_flag
        ,p_sub_leaf_flag => g_crrnt_chain(p_level).leaf_node);
Line: 367

END insert_chain;
Line: 379

  UPDATE hri_cs_suph
  SET effective_end_date = p_end_date
  WHERE sub_person_id = p_person_id
  AND p_end_date BETWEEN effective_start_date AND effective_end_date;
Line: 400

  SELECT
   effective_start_date
  ,effective_end_date
  FROM hri_cs_suph
  WHERE sub_person_id = g_crrnt_chain(p_level).person_id
  AND g_crrnt_chain_start_date
    BETWEEN effective_start_date AND effective_end_date;
Line: 410

  SELECT
    MIN(effective_start_date)   next_chain_start_date
  FROM hri_cs_suph
  WHERE sub_person_id = g_crrnt_chain(p_level).person_id
  AND effective_start_date > g_crrnt_chain_start_date;
Line: 455

    UPDATE hri_cs_suph
    SET effective_end_date = g_crrnt_chain_start_date - 1
    WHERE sub_person_id =
             g_crrnt_chain(p_level).person_id
    AND effective_start_date = l_existing_chain_start;
Line: 461

/* Delete existing chain if it is the same date as the current */
  ELSIF (l_existing_chain_start = g_crrnt_chain_start_date) THEN
    g_chain_transactions := g_chain_transactions + 1;
Line: 464

  /* Delete existing chain */
  /* Bug 2670477 - join by person id */
    DELETE FROM hri_cs_suph
    WHERE sub_person_id = g_crrnt_chain(p_level).person_id
    AND effective_start_date = l_existing_chain_start;
Line: 472

/* Insert new chain */
  insert_chain(p_level => p_level
              ,p_end_date => l_chain_end_date);
Line: 476

/* Remove any obsolete chain updates */
  BEGIN
    IF (g_final_date_tab(g_crrnt_chain(p_level).person_id) IS NOT NULL) THEN
      g_chain_transactions := g_chain_transactions + 1;
Line: 481

      DELETE FROM hri_cs_suph
      WHERE sub_person_id = g_crrnt_chain(p_level).person_id
      AND effective_start_date > g_final_date_tab(g_crrnt_chain(p_level).person_id);
Line: 501

  SELECT actual_termination_date, final_process_date
  FROM per_periods_of_service
  WHERE period_of_service_id = p_period_of_service_id;
Line: 553

  SELECT 'N'
  FROM per_all_assignments_f asg
  WHERE asg.supervisor_id = g_fetch_sup_id(p_index)
  AND asg.assignment_type = 'E'
  AND asg.primary_flag = 'Y'
  AND p_change_date - 1
         BETWEEN asg.effective_start_date AND asg.effective_end_date;
Line: 584

    /* Get the end date to insert for the new top manager record */
      l_end_date := get_end_date
                (p_index => p_index
                ,p_person_id => g_crrnt_chain(1).person_id
                ,p_period_of_service_id => g_crrnt_chain_top_pos_id
                ,p_change_date => p_change_date);
Line: 597

    /* Insert chain link in historical hierarchy table for new top  */
    /* level manager */
      process_chain(p_level => 1,
                    p_end_date => l_end_date);
Line: 609

/* Inserts and stores the chain of the current supervisor change person       */
/******************************************************************************/
FUNCTION insert_supv_change( p_index        IN NUMBER,
                             p_change_date  IN DATE,
                             p_event_code   IN VARCHAR2)
                  RETURN PLS_INTEGER IS

/***********************************************************************/
/* Cursor picking all managers above person who has changed supervisor */
/* LEVEL (wrt this cursor) will be 1 for this person                   */
/* Rows are returned with the topmost supervisor first                 */
/***********************************************************************/
  CURSOR new_manager_chain_csr IS
  SELECT
   hier.business_group_id
  ,hier.person_id
  ,hier.assignment_id
  ,hier.assignment_status_type_id   asg_status_id
  ,hier.supervisor_id
  ,hier.period_of_service_id
  ,hier.primary_flag
  ,LEVEL relative_level
  FROM (SELECT
         asg.business_group_id
        ,asg.person_id
        ,asg.assignment_id
        ,asg.assignment_status_type_id
        ,asg.supervisor_id
        ,asg.period_of_service_id
        ,asg.primary_flag
        FROM
         per_all_assignments_f        asg
        WHERE asg.assignment_type = 'E'
        AND asg.primary_flag = 'Y'
        AND p_change_date
          BETWEEN asg.effective_start_date AND asg.effective_end_date) hier
  START WITH hier.assignment_id = g_fetch_asg_id(p_index)
  CONNECT BY hier.person_id = PRIOR hier.supervisor_id
  ORDER BY relative_level desc;
Line: 735

/* If the insert is for a non-terminated level 2 supervisor then */
/* potentially the top level supervisor could be new. */
  IF (l_person_level = 2 AND p_event_code <> 'TERM') THEN
    test_top_supervisor(p_index => p_index,
                        p_change_date => p_change_date,
                        p_event_code => p_event_code);
Line: 751

      /* Update immediate supervisor to non-leaf node */
        null;
Line: 778

END insert_supv_change;
Line: 784

PROCEDURE update_sub_chains( p_min_lvl     IN NUMBER,
                             p_max_lvl     IN NUMBER,
                             p_index       IN NUMBER) IS

BEGIN

  FOR v_sub_lvl IN p_min_lvl..p_max_lvl LOOP

    process_chain(p_level => v_sub_lvl,
                  p_end_date => g_crrnt_chain_end_date);
Line: 797

END update_sub_chains;
Line: 800

/* Updates all subordinates of the current supervisor change person           */
/* The cursor tree walk returns rows on a depth first basis. The global chain */
/* is kept updated with the latest information returned. For example, suppose */
/* the supervisor labelled X below changed supervisor. The subordinates of X  */
/* would be returned in the order they are numbered. This means that when 2   */
/* is processed it is guaranteed that the global chain will contain the       */
/* correct information for X and above, and then for 1 and 2.                 */
/*                                                                            */
/*                       X                                                    */
/*                      / \                                                   */
/*                     1   4                                                  */
/*                    / \                                                     */
/*                   2   3                                                    */
/*                                                                            */
/* A breadth first tree walk would return the subordinates of X in the order  */
/* 1 -> 4 -> 2 -> 3. This would mean that when 2 is processed the global      */
/* chain would contain information for X and above, and then for 4 and 2.     */
/* This would be wrong!!!                                                     */
/******************************************************************************/
PROCEDURE update_subordinates( p_index        IN NUMBER,
                               p_change_date  IN DATE,
                               p_event_code   IN VARCHAR2) IS

/* Cursor picks out all subordates of the person who has changed supervisor  */
/* so that the chains of the subordinates can all be updated with the change */
/* This cursor MUST return rows in the default order                         */
  CURSOR subordinates_csr IS
  SELECT
   hier.business_group_id
  ,hier.person_id
  ,hier.assignment_id
  ,hier.assignment_status_type_id  asg_status_id
  ,hier.supervisor_id
  ,hier.period_of_service_id
  ,hier.primary_flag
  ,LEVEL-1+g_crrnt_chain_owner_lvl   actual_level
  FROM (SELECT
        asg.business_group_id
       ,asg.person_id
       ,asg.assignment_id
       ,asg.assignment_status_type_id
       ,asg.period_of_service_id
       ,asg.supervisor_id
       ,asg.primary_flag
       FROM
        per_all_assignments_f        asg
       WHERE asg.assignment_type = 'E'
       AND asg.primary_flag = 'Y'
       AND p_change_date
         BETWEEN asg.effective_start_date AND asg.effective_end_date) hier
  WHERE hier.person_id <> g_fetch_psn_id(p_index)
  START WITH hier.person_id = g_fetch_psn_id(p_index)
  CONNECT BY hier.supervisor_id = PRIOR hier.person_id;
Line: 932

      /* If the end of a chain is reached then insert it */
        IF (l_fetch_level(i) <= l_last_sub_lvl) THEN

        /* Insert the changed subordinate chains */
          update_sub_chains(p_min_lvl  => l_fetch_level(i),
                            p_max_lvl  => l_last_sub_lvl,
                            p_index    => p_index);
Line: 994

  /* Insert the changed subordinate chains */
    update_sub_chains(p_min_lvl  => g_crrnt_chain_owner_lvl+1,
                      p_max_lvl  => l_last_sub_lvl,
                      p_index    => p_index);
Line: 1018

END update_subordinates;
Line: 1021

/* Updates stored leaf node information                                       */
/******************************************************************************/
PROCEDURE update_leaf_node_change( p_person_id        IN NUMBER,
                                   p_change_date      IN DATE,
                                   p_from_leaf_flag   IN VARCHAR2,
                                   p_to_leaf_flag     IN VARCHAR2) IS

/* Selects single link in chain for a non-terminated supervisor on a date */
  CURSOR chain_csr IS
  SELECT *
  FROM hri_cs_suph
  WHERE sub_person_id = p_person_id
  AND sup_person_id = p_person_id
  AND sub_invalid_flag_code = 'N'
  AND sub_leaf_flag_code = p_from_leaf_flag
  AND p_change_date BETWEEN effective_start_date AND effective_end_date;
Line: 1042

  /* If the start dates match then update the existing chain */
    IF (chain_rec.effective_start_date = p_change_date) THEN

      g_chain_transactions := g_chain_transactions + 1;
Line: 1047

    /* Update all links in chain at once */
      UPDATE hri_cs_suph
      SET sub_leaf_flag_code = p_to_leaf_flag
      WHERE sub_person_id = p_person_id
      AND effective_start_date = p_change_date
      AND sub_invalid_flag_code = 'N';
Line: 1054

    /* Otherwise end date existing chain and insert new one */
      ELSE

        g_chain_transactions := g_chain_transactions + 2;
Line: 1059

      /* Insert new chain */
        INSERT INTO hri_cs_suph
          (sup_business_group_id
          ,sup_person_id
          ,sup_assignment_id
          ,sup_assignment_status_type_id
          ,sup_level
          ,sup_invalid_flag_code
          ,sub_business_group_id
          ,sub_person_id
          ,sub_assignment_id
          ,sub_assignment_status_type_id
          ,sub_primary_asg_flag_code
          ,sub_level
          ,sub_relative_level
          ,sub_invalid_flag_code
          ,orphan_flag_code
          ,sub_leaf_flag_code
          ,effective_start_date
          ,effective_end_date)
          SELECT
           sup_business_group_id
          ,sup_person_id
          ,sup_assignment_id
          ,sup_assignment_status_type_id
          ,sup_level
          ,sup_invalid_flag_code
          ,sub_business_group_id
          ,sub_person_id
          ,sub_assignment_id
          ,sub_assignment_status_type_id
          ,sub_primary_asg_flag_code
          ,sub_level
          ,sub_relative_level
          ,sub_invalid_flag_code
          ,orphan_flag_code
          ,p_to_leaf_flag
          ,p_change_date
          ,chain_rec.effective_end_date
          FROM hri_cs_suph
          WHERE sub_person_id = p_person_id
          AND effective_start_date = chain_rec.effective_start_date
          AND sub_invalid_flag_code = 'N';
Line: 1104

        UPDATE hri_cs_suph
        SET effective_end_date = p_change_date - 1
        WHERE sub_person_id = p_person_id
        AND effective_start_date = chain_rec.effective_start_date
        AND sub_invalid_flag_code = 'N';
Line: 1114

END update_leaf_node_change;
Line: 1125

  SELECT
   asg.assignment_id                assignment_id
  ,asg.effective_start_date         asg_start
  ,asg.effective_end_date           asg_end
  ,asg.business_group_id            business_group_id
  ,asg.person_id                    person_id
  ,NVL(asg.supervisor_id , -1)      supervisor_id
  ,DECODE(prev_asg.assignment_id,
            to_number(null), to_number(null),
          NVL(prev_asg.supervisor_id, -1))  prev_supervisor_id
  ,asg.assignment_status_type_id    assignment_status_type_id
  ,pos.period_of_service_id         period_of_service_id
  ,asg.effective_start_date         change_date
  ,DECODE(asg.effective_start_date,
            pos.date_start, 'HIRE',
          'CHNG')                   event_code
  ,pos.actual_termination_date      termination_date
  ,pos.final_process_date           final_process_date
  FROM
   per_all_assignments_f        asg
  ,per_periods_of_service       pos
  ,per_all_assignments_f        prev_asg
  WHERE asg.primary_flag = 'Y'
  AND prev_asg.primary_flag (+) = 'Y'
  AND asg.assignment_type  = 'E'
  AND prev_asg.assignment_type (+) = 'E'
  AND asg.period_of_service_id = pos.period_of_service_id (+)
  AND prev_asg.person_id (+) = asg.person_id
  AND prev_asg.effective_end_date (+) = asg.effective_start_date - 1
/* All non-terminated assignment supervisor changes within date range */
  AND ((asg.effective_start_date BETWEEN p_collect_from AND p_collect_to
        AND NVL(asg.supervisor_id, -1) <> NVL(prev_asg.supervisor_id, -1)
        AND NVL(prev_asg.assignment_id, -1) <> -1
        AND asg.effective_start_date <= NVL(pos.actual_termination_date, g_current_date))
/* All initial hire assignments with a supervisor */
    OR (asg.effective_start_date = pos.date_start
        AND pos.date_start BETWEEN p_collect_from AND p_collect_to
        AND asg.supervisor_id IS NOT NULL))
  UNION ALL
/* All terminations and final processes */
  SELECT /*+ leading(pos) use_hash(pos asg) */
   asg.assignment_id                assignment_id
  ,asg.effective_start_date         asg_start
  ,asg.effective_end_date           asg_end
  ,asg.business_group_id            business_group_id
  ,asg.person_id                    person_id
  ,to_number(null)                  supervisor_id
  ,NVL(asg.supervisor_id , -1)      prev_supervisor_id
  ,asg.assignment_status_type_id    assignment_status_type_id
  ,pos.period_of_service_id         period_of_service_id
  ,pos.actual_termination_date + 1  change_date
  ,'TERM'                           event_code
  ,pos.actual_termination_date      termination_date
  ,pos.final_process_date           final_process_date
  FROM
   per_all_assignments_f        asg
  ,per_periods_of_service       pos
  WHERE asg.effective_end_date = pos.actual_termination_date
  AND (pos.actual_termination_date BETWEEN p_collect_from AND p_collect_to
    OR pos.final_process_date BETWEEN p_collect_from AND p_collect_to)
  AND asg.period_of_service_id = pos.period_of_service_id
  UNION ALL
/* All subordinates of supervisors who have separated (final process) */
/* whose assignments have not been updated with a new supervisor and so */
/* are invalid */
  SELECT /*+ leading(pps) use_hash(pps sub_asg sub_pps) */
   sub_asg.assignment_id                assignment_id
  ,sub_asg.effective_start_date         asg_start
  ,sub_asg.effective_end_date           asg_end
  ,sub_asg.business_group_id            business_group_id
  ,sub_asg.person_id                    person_id
  ,to_number(null)                      supervisor_id
  ,sub_asg.supervisor_id                prev_supervisor_id
  ,sub_asg.assignment_status_type_id    assignment_status_type_id
  ,sub_pps.period_of_service_id         period_of_service_id
  ,pps.final_process_date + 1           change_date
/* Event code ORPH for subordinates orphaned by their supervisor's separation */
  ,'ORPH'                               event_code
  ,sub_pps.actual_termination_date      actual_termination_date
  ,sub_pps.final_process_date           final_process_date
  FROM
   per_all_assignments_f  sub_asg
  ,per_periods_of_service pps
  ,per_periods_of_service sub_pps
  WHERE pps.final_process_date BETWEEN p_collect_from AND p_collect_to
  AND sub_asg.supervisor_id = pps.person_id
  AND sub_asg.period_of_service_id = sub_pps.period_of_service_id
  AND sub_asg.assignment_type = 'E'
  AND sub_asg.primary_flag = 'Y'
  AND pps.final_process_date + 1
    BETWEEN sub_asg.effective_start_date AND sub_asg.effective_end_date
  ORDER BY change_date;
Line: 1286

          l_return_code := insert_supv_change(p_index => i
                                             ,p_change_date => g_fetch_chng_dt(i)
                                             ,p_event_code => 'ORPH');
Line: 1289

        /* If no error encountered then update chains for all their subordinates */
          IF (l_return_code = 0) THEN
          /* Process subordinates for assignment */
            update_subordinates(p_index => i
                               ,p_change_date => g_fetch_chng_dt(i)
                               ,p_event_code => 'ORPH');
Line: 1295

          /* Insert chain for assignment */
            process_chain(p_level => g_crrnt_chain_owner_lvl,
                          p_end_date => g_crrnt_chain_end_date);
Line: 1317

          l_return_code := insert_supv_change(p_index => i
                                             ,p_change_date => g_fetch_chng_dt(i)
                                             ,p_event_code => 'HIRE');
Line: 1326

          /* Update new hire's manager to be a non-leaf node */
          /* if they weren't before */
            update_leaf_node_change(p_person_id => g_fetch_sup_id(i),
                                    p_change_date => g_fetch_chng_dt(i),
                                    p_from_leaf_flag => 'Y',
                                    p_to_leaf_flag => 'N');
Line: 1333

            update_subordinates(p_index => i
                               ,p_change_date => g_fetch_chng_dt(i)
                               ,p_event_code => 'HIRE');
Line: 1336

          /* Insert chain for new hire */
            process_chain(p_level => g_crrnt_chain_owner_lvl,
                          p_end_date => g_crrnt_chain_end_date);
Line: 1354

          /* If not then update chain */
            IF (l_leaf_flag = 'Y') THEN
              update_leaf_node_change(p_person_id => g_fetch_prev_sup_id(i),
                                      p_change_date => g_fetch_strt_dt(i),
                                      p_from_leaf_flag => 'N',
                                      p_to_leaf_flag => 'Y');
Line: 1368

          l_return_code := insert_supv_change(p_index => i
                                             ,p_change_date => g_fetch_strt_dt(i)
                                             ,p_event_code => 'CHNG');
Line: 1371

        /* If no error encountered then update chains for all their subordinates */
          IF (l_return_code = 0) THEN
          /* Process subordinates for assignment */
            update_subordinates(p_index => i
                               ,p_change_date => g_fetch_strt_dt(i)
                               ,p_event_code => 'CHNG');
Line: 1377

          /* Insert chain for assignment */
            process_chain(p_level => g_crrnt_chain_owner_lvl,
                          p_end_date => g_crrnt_chain_end_date);
Line: 1380

          /* Update new manager to be a non-leaf node */
          /* if they weren't before */
            update_leaf_node_change(p_person_id => g_fetch_sup_id(i),
                                    p_change_date => g_fetch_strt_dt(i),
                                    p_from_leaf_flag => 'Y',
                                    p_to_leaf_flag => 'N');
Line: 1392

          /* If not then update chain */
            IF (l_leaf_flag = 'Y') THEN
              update_leaf_node_change(p_person_id => g_fetch_prev_sup_id(i),
                                      p_change_date => g_fetch_strt_dt(i),
                                      p_from_leaf_flag => 'N',
                                      p_to_leaf_flag => 'Y');
Line: 1426

            /* If the terminated supervisor is still supervising, update their chain */
            /* and those of all their subordinates */
              IF (l_leaf_flag = 'N') THEN
              /* Calculate new chain for terminated supervisor */
                l_return_code := insert_supv_change(p_index => i
                                                   ,p_change_date => g_fetch_term_dt(i) + 1
                                                   ,p_event_code => 'TERM');
Line: 1433

              /* If no error encountered then update chains for all their subordinates */
                IF (l_return_code = 0) THEN
                /* Process subordinates for assignment */
                  update_subordinates(p_index => i
                                     ,p_change_date => g_fetch_term_dt(i) + 1
                                     ,p_event_code => 'TERM');
Line: 1439

                /* Insert chain for assignment */
                  process_chain(p_level => g_crrnt_chain_owner_lvl,
                                p_end_date => g_crrnt_chain_end_date);
Line: 1453

          /* If not then update chain */
            IF (l_leaf_flag = 'Y') THEN
              update_leaf_node_change(p_person_id => g_fetch_prev_sup_id(i),
                                      p_change_date => g_fetch_term_dt(i) + 1,
                                      p_from_leaf_flag => 'N',
                                      p_to_leaf_flag => 'Y');
Line: 1519

/* Insert new supervisor hierarchy history records */
  collect_data
    (p_collect_from => TRUNC(p_start_date)
    ,p_collect_to   => TRUNC(p_end_date));
Line: 1527

  output('Updated Supervisor History table:  '  ||
         to_char(sysdate,'HH24:MI:SS'));