SAP HCM OM

From SapWiki

Transacciones

  1. PP01 Actual.datos plan (guiado por menú)
  2. PO10 Actualizar unidad de organización
  3. PO03 Actualizar función
  4. PO13 Actualizar posición
  5. PO01 Actualizar puesto de trabajo
  • Reportes
  1. RHGRENZ0 - Delimitar objetos
  2. RHCHECKRELATIONS - Borrado de enlaces sin objetos existentes
  3. RHCHECK1 - Verif.consistencia base datos

FM OM Infotypes

RH_OBJECT_CREATE

CALL FUNCTION 'RH_OBJECT_CREATE'
  EXPORTING
    plvar               = '01'
    otype               = 'S'
    short               = ls_p1000-short
    stext               = ls_p1000-stext
    begda               = p_begda
    endda               = p_endda
    vtask               = 'B'
  IMPORTING
    objid               = p_objid_new
  EXCEPTIONS
    text_required       = 1
    invalid_otype       = 2
    invalid_date        = 3
    error_during_insert = 4
    error_ext_number    = 5
    undefined           = 6
    OTHERS              = 7.
IF sy-subrc <> 0.
  ROLLBACK WORK.
  p_subrc = 7.
  RETURN.
ENDIF.
 

RH_DELETE_OBJECT

FORM borrar_relaciones USING p_objid.

  DATA: lt_p1001 TYPE TABLE OF p1001 WITH HEADER LINE,
        l_objid  TYPE p1000-objid.

  CALL FUNCTION 'RH_READ_INFTY'
    EXPORTING
      plvar                = '01'
      otype                = 'ZT'
      objid                = p_objid
      infty                = '1001'
      istat                = '1'
    TABLES
      innnn                = lt_p1001
*     OBJECTS              =
    EXCEPTIONS
      all_infty_with_subty = 1
      nothing_found        = 2
      no_objects           = 3
      wrong_condition      = 4
      wrong_parameters     = 5
      OTHERS               = 6.
  IF sy-subrc <> 0.
* MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
*         WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
  ENDIF.

  LOOP AT lt_p1001 WHERE sclas = 'ZI'.
    MOVE lt_p1001-sobid TO l_objid.

    CALL FUNCTION 'RH_DELETE_OBJECT'
      EXPORTING
        plvar                        = '01'
        otype                        = 'ZI'
        objid                        = l_objid
        vtask                        = 'B'
      EXCEPTIONS
        error_during_delete          = 1
        no_authorization             = 2
        corr_exit                    = 3
        buffer_upd_with_foreign_data = 4
        OTHERS                       = 5.
  ENDLOOP.

  CALL FUNCTION 'RH_UPDATE_DATABASE'
    EXPORTING
      vtask        = 'D'
      commit_flg   = 'X'  "VWMCOMMIT
      clear_buffer = ' '
    EXCEPTIONS
      corr_exit    = 04.
ENDFORM.                    " BORRAR_

RH_INSERT_INFTY

FORM insert_infty USING p_p TYPE any
               CHANGING p_subrc TYPE sy-subrc.

  DATA: wplog_record_tab TYPE TABLE OF wplog,
        wplog_record     TYPE          wplog.

  FIELD-SYMBOLS <wplog> TYPE c.

  ASSIGN p_p TO <wplog> CASTING.
  wplog_record = <wplog>.

  APPEND wplog_record TO wplog_record_tab.

  CALL FUNCTION 'RH_INSERT_INFTY'
    EXPORTING
      vtask               = 'B'
    TABLES
      innnn               = wplog_record_tab
    EXCEPTIONS
      no_authorization    = 1
      error_during_insert = 2
      repid_form_initial  = 2
      corr_exit           = 2
      OTHERS              = 2.

  p_subrc = sy-subrc.

ENDFORM.                    "insert_infty

PERFORM insert_infty USING ls_P1010
                  CHANGING l_subrc.
IF l_subrc <> 0.
  ROLLBACK WORK.
  p_subrc = 5.
  RETURN.
ENDIF.

RH_DELETE_INFTY

FORM delete_infotype USING p_p TYPE any
                  CHANGING p_subrc TYPE sy-subrc.
  DATA: wplog_record_tab TYPE TABLE OF wplog,
        wplog_record     TYPE          wplog.

  FIELD-SYMBOLS <wplog> TYPE c.

  ASSIGN p_p TO <wplog> CASTING.
  wplog_record = <wplog>.

  APPEND wplog_record TO wplog_record_tab.

  CALL FUNCTION 'RH_DELETE_INFTY'
    EXPORTING
      vtask               = 'B'
    TABLES
      innnn               = wplog_record_tab
    EXCEPTIONS
      error_during_delete = 1
      no_authorization    = 2
      delete_first_record = 3
      corr_exit           = 4
      OTHERS              = 5.
  p_subrc = sy-subrc.

ENDFORM.                    "delete_infotype

.

PERFORM delete_infotype USING ls_p9005
                     CHANGING l_subrc.
IF l_subrc <> 0.
  ROLLBACK WORK.
  p_subrc = 5.
  RETURN.
ENDIF.

Leer Descripción de Objeto RH_OBJECT_DESCRIPTION_READ_2

FORM read_description USING p_objid
                            p_otype
                            p_begda
                            p_endda
                            p_subty
                            p_seqnr
                    CHANGING p_longtext TYPE wcb_tdline_tab.

  DATA: i1002 TYPE TABLE OF p1002,
        i1002_exp TYPE TABLE OF p1002_exp WITH HEADER LINE,
         objects TYPE TABLE OF hrobject WITH HEADER LINE.
  DATA ls_longtext LIKE LINE OF p_longtext.

  objects-plvar = c_actual.
  objects-otype = p_otype.
  objects-objid = p_objid.
  APPEND objects.

* read appraisal information and rating description
  CALL FUNCTION 'RH_OBJECT_DESCRIPTION_READ_2'
       EXPORTING
*           LANGU         = SY-LANGU
            begda         = p_begda
            endda         = p_endda
            subty         = p_subty
       TABLES
            i1002         = i1002
            i1002_exp     = i1002_exp
            OBJECTS       = OBJECTS
       exceptions
            nothing_found = 1
            infty_empty   = 2
            undefined     = 3
            OTHERS        = 4.
  IF sy-subrc <> 0.
    CLEAR: i1002,
           i1002_exp.
  ENDIF.


  LOOP AT i1002_exp WHERE subty <> p_subty OR seqnr <> p_seqnr
                       OR begda <> p_begda OR endda <> p_endda.
    DELETE i1002_exp INDEX sy-tabix.
  ENDLOOP.

  LOOP AT i1002_exp.
    MOVE i1002_exp-tline TO ls_longtext.
    APPEND ls_longtext TO p_longtext.
  ENDLOOP.
ENDFORM.                    "read_description
.
.
.

DATA: lt_p1002    TYPE TABLE OF p1002 WITH HEADER LINE,
      lt_relation TYPE hri1001_tab,
      lt_longtext TYPE wcb_tdline_tab.
DATA ls_p1002 LIKE LINE OF lt_p1002.
DATA l_subrc TYPE sy-subrc.

CALL FUNCTION 'RH_READ_INFTY'
  EXPORTING
    plvar                = '01'
    otype                = 'S'
    objid                = p_objid
    infty                = '1002'
  TABLES
    innnn                = lt_p1002
  EXCEPTIONS
    all_infty_with_subty = 1
    nothing_found        = 2
    no_objects           = 3
    wrong_condition      = 4
    wrong_parameters     = 5
    OTHERS               = 6.

LOOP AT lt_p1002 INTO ls_p1002 WHERE istat = '1'.
ENDLOOP.
IF sy-subrc = 0.
  PERFORM read_description IN PROGRAM zhr_sindicato_rutinas
                    USING p_objid
                          ls_p1002-otype
                          ls_p1002-begda
                          ls_p1002-endda
                          ls_p1002-subty
                          ls_p1002-seqnr
                 CHANGING lt_longtext[].
ENDIF.

RH_OBJECT_DESCRIPTION_WRITE

CALL FUNCTION 'RH_OBJECT_DESCRIPTION_WRITE'
  EXPORTING
    plvar                = '01'
    otype                = 'S'
    objid                = p_objid
    begda                = ls_p1002-begda
    endda                = ls_p1002-endda
    subty                = ls_p1002-subty
    vtask                = 'B'
  TABLES
    ptxt1002             = lt_longtext
  EXCEPTIONS
    object_not_found     = 1
    description_required = 2
    no_authority         = 3
    error_during_insert  = 4
    invalid_date         = 5
    undefined            = 6
    OTHERS               = 7.
IF sy-subrc <> 0.
  ROLLBACK WORK.
  l_subrc = 5.
  RETURN.
ENDIF.

Crear Relación

 FORM relation_ CHANGING p_subrc.
    DATA lt_relation TYPE hri1001_tab.
    DATA ls_relation LIKE LINE OF lt_relation.
    DATA l_subty LIKE ls_relation-relat.

    DATA: l_objid TYPE p1000-objid,
          l_otype TYPE p1000-otype.
    DATA l_like(20).

    CLEAR ls_relation.
    ls_relation-mandt = sy-mandt.
    ls_relation-plvar = '01'.
    ls_relation-otype = g_otype.
    ls_relation-objid = p1000-objid.
    ls_relation-infty = '1001'.
    ls_relation-istat = '1'.
    ls_relation-rsign = 'B'.
    ls_relation-relat = l_subty.                            "'Z01'.
    ls_relation-begda = p1000-begda.
    ls_relation-endda = p1000-endda.
    ls_relation-sclas = p_otype.
    ls_relation-sobid = p_objid.

    APPEND ls_relation TO lt_relation.

    PERFORM crea_relacion USING lt_relation CHANGING p_subrc.
    if p_subrc = 0.
      CALL FUNCTION 'RH_UPDATE_DATABASE'
        EXPORTING
          vtask        = 'D'
          commit_flg   = 'X'  "VWMCOMMIT
          clear_buffer = ' '
        EXCEPTIONS
          corr_exit    = 04.
    endif.

  ENDFORM.                    "relation_fiscalizacion
  
  FORM crea_relacion USING p_relation TYPE hri1001_tab CHANGING p_subrc.

  CALL FUNCTION 'RH_RELATION_WRITE'
   EXPORTING
     vtask                      = 'B'
*     KEEP_LUPD                  = ' '
    TABLES
      relation                   = p_relation
*     ERR_RELATION               =
   EXCEPTIONS
     no_authority               = 1
     relation_not_allowed       = 2
     object_not_found           = 3
     wrong_date_format          = 4
     time_not_valid             = 5
     error_during_insert        = 6
     undefined                  = 7
     OTHERS                     = 8
            .

  p_subrc = sy-subrc.

ENDFORM.                    "crea_relacion

Ayuda Busqueda para Objeto

En dynpro (include MH5A0I50)

module objid_request_5000 input.
  self_repid = sy-repid.
  self_dynnr = sy-dynnr.

  call function 'RH_OBJID_REQUEST'
       exporting
            plvar                 = pphdr-plvar
            otype                 = pphdr-otype
            dynpro_repid          = self_repid
            dynpro_dynnr          = self_dynnr
            dynpro_plvarfield     = 'PPHDR-PLVAR'
            dynpro_otypefield     = 'PPHDR-OTYPE'
            dynpro_searkfield     = 'PM0D1-SEARK'
       importing
            sel_object            = f4_objec
       exceptions
            cancelled             = 1
            wrong_condition       = 2
            nothing_found         = 3
            illegal_mode          = 4
            internal_error        = 5
            others                = 6.

  if sy-subrc = 0.
    move f4_objec-realo to pm0d1-seark.
    if pphdr-otype = 'K'.
      clear pm0d1-seark+10(2).
    endif.
  endif.
endmodule.                    "objid_request_5000 INPUT

En Dynpro

process on value-request.
  field pm0d1-seark module objid_request_5000. 

En reporte (ver programa S_HRPA_QA_MERGE_JOB_FAMILY)

FORM get_object_f4 USING lp_otype TYPE otype
                           lp_field TYPE char50.

  DATA : lw_object   TYPE objec,
         lt_dynfield TYPE TABLE OF dynpread,
         lw_dynfield LIKE LINE  OF lt_dynfield.

  FIELD-SYMBOLS <fs_field> TYPE any.

  CALL FUNCTION 'RH_OBJID_REQUEST'
    EXPORTING
      plvar           = c_01
      otype           = lp_otype
      seark           = '*'
      orgbeg          = p_begda
      orgend          = p_begda
    IMPORTING
      sel_object      = lw_object
    EXCEPTIONS
      cancelled       = 1
      wrong_condition = 2
      nothing_found   = 3
      internal_error  = 4
      illegal_mode    = 5
      OTHERS          = 6.
  IF sy-subrc IS INITIAL.
    ASSIGN (lp_field) TO <fs_field>.
    <fs_field> = lw_object-objid.
    IF lp_field EQ 'P_SOBID'.
      p_shortt = lw_object-short.
      p_stextt = lw_object-stext.

      lw_dynfield-fieldname  = 'P_SHORTT'.
      lw_dynfield-fieldvalue = p_shortt.
      APPEND lw_dynfield TO lt_dynfield.

      lw_dynfield-fieldname  = 'P_STEXTT'.
      lw_dynfield-fieldvalue = p_stextt.
      APPEND lw_dynfield TO lt_dynfield.
    ELSEIF lp_field EQ 'P_JOBF1'.
      p_jobf1s = lw_object-short.
      p_jobf1l = lw_object-stext.

      lw_dynfield-fieldname  = 'P_JOBF1S'.
      lw_dynfield-fieldvalue = p_jobf1s.
      APPEND lw_dynfield TO lt_dynfield.

      lw_dynfield-fieldname  = 'P_JOBF1L'.
      lw_dynfield-fieldvalue = p_jobf1l.
      APPEND lw_dynfield TO lt_dynfield.
    ELSEIF lp_field EQ 'P_JOBF2'.
      p_jobf2s = lw_object-short.
      p_jobf2l = lw_object-stext.

      lw_dynfield-fieldname  = 'P_JOBF2S'.
      lw_dynfield-fieldvalue = p_jobf2s.
      APPEND lw_dynfield TO lt_dynfield.

      lw_dynfield-fieldname  = 'P_JOBF2L'.
      lw_dynfield-fieldvalue = p_jobf2l.
      APPEND lw_dynfield TO lt_dynfield.

    ENDIF.
    CALL FUNCTION 'DYNP_VALUES_UPDATE'
      EXPORTING
        dyname               = sy-cprog
        dynumb               = sy-dynnr
      TABLES
        dynpfields           = lt_dynfield
      EXCEPTIONS
        invalid_abapworkarea = 1
        invalid_dynprofield  = 2
        invalid_dynproname   = 3
        invalid_dynpronummer = 4
        invalid_request      = 5
        no_fielddescription  = 6
        undefind_error       = 7
        OTHERS               = 8.
    IF sy-subrc IS NOT INITIAL.
      MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
              WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
    ENDIF.

  ELSE.
    IF lp_field EQ 'P_SOBID'.
      CLEAR : p_shortt, p_stextt.
    ELSEIF lp_field EQ 'P_JOBF1'.
      CLEAR : p_jobf1s, p_jobf1l.
    ELSEIF lp_field EQ 'P_JOBF2'.
      CLEAR : p_jobf2s, p_jobf2l.
    ENDIF.
  ENDIF.

ENDFORM. " GET_OBJECT_F4

AT SELECTION-SCREEN ON VALUE-REQUEST FOR p_sobid.
  PERFORM get_object_f4 USING c_fn 'P_SOBID'.