sapdev logo background
sapdev logo sapdev logo
Comments

Add n number of working days to date (using personal work schedule)




Z version of SAP report 'RPTPSH10' which exports data to memory ID rather than displaying data on screen as report. This data can then be imported into the calling program for manipulation or reading.

zrptpsh10_list_to_memory. " Copy of SAP report 'rptpsh10'
include <icon>.
type-pools vclty.
tables: pernr,
        t001p,
        t550a.

infotypes: 0000,
           0001,
           0002,
           0007,
           2001 mode n,                "Absences
           2002 mode n,                "Attendance
           2003 mode n,                "Substitution
           2004 mode n,                "On-Call Duty
           2005 mode n.                "Overtime
*
data: DBA_SELLIST_CLUSTER type VCLTY_SELLIST_TABLE with header line,
      ert         like hrerror    occurs 0 with header line,
      psp         like ptpsp      occurs 0 with header line,
      dayint      like pwsdayint  occurs 0 with header line,
      daygen      like pwsdaygen  occurs 0 with header line,
      i2003       like p2003      occurs 0 with header line.
*
data: begin of fields occurs 0,
        co1(60),  co2(60),  co3(60), co4(60),
      end of fields.

data: timefields like fields occurs 0 with header line.

data: begin of hd occurs 0,
      pernr like pernr-pernr,
      name(40),
      inv_menge like pakey-seqnr,      "ALV copies only 20 columns!
      moabw like t001p-moabw,                               "
      mover like t001p-mover,          "ALV copies only 20 columns!
      datum like psp-datum,
      kurzt like t246-kurzt,
      tprog like psp-tprog,
      varia like psp-varia,
       ttext like t550s-ttext,
      vtart like p2003-vtart,
       vtext like t556t-vtext,
      motpr like psp-motpr,
      sobeg(8),
      soend(8),
      stdaz like PTEV_REP_H-stdaz,
      ftkla like psp-ftkla,
      tagty like psp-tagty,
       tatxt like t553t-langt,
      zmodn like psp-zmodn,
       ptext like t551s-ztext,
      mofid like t508a-mofid,
       ftext like thoct-ltext,
      menge like PTEV_REP_H-itanz,
      alvmarker type rp_xfeld,
      end of hd.

data: hd_sel like hd occurs 0 with header line.

data: begin of hd_vert,                "XLTL9CK018334 "note 322021
        pernr like hd-pernr,
        name  like hd-name,
        mover like hd-mover,
        motpr like hd-motpr,
        stdaz like hd-stdaz,
      end of hd_vert.

data: begin of i200x occurs 0,
        pernr like pernr-pernr,
        name(40),
        datum like psp-datum,
        infty like pskey-infty,
        itext like t582s-itext,
        subty like pskey-subty,
        atext like t554t-atext,
        begda like pskey-begda,
        endda like pskey-endda,
        beguz(8),
        enduz(8),
        stdaz(5),
     end of i200x.
*
data: i200x_sel   like i200x      occurs 0 with header line.


data: begin of errortexts occurs 0,
        text(100),
      end of errortexts.
*
data: error_begda(10), error_endda(10).
*
data: wotnr type i,
      $edit-name(23),
      $ret-code like sy-subrc,
      ret_cd like sy-subrc,
      entries type i,
      error_message(50).               "concatenate for T100

data:report_begda like pn-begda,
     pro_beg type i, pro_end type i.

data: sw_active(1) value ' ',
      switch_active,
      single_line.

data: header_line1(69).                "XLTL9CK002809

data hlp_pn_endda like pn-endda.       "XLTL9CK018334
data l_mofid like hd-mofid."NOTE604361
*
selection-screen begin of block param with frame title text-fra.
selection-screen begin of line.
selection-screen position 2.
parameters: rdclust type rdclst.
selection-screen comment 5(25) text-ta0 for field rdclust.
selection-screen end   of line.
selection-screen end of block param.
*
selection-screen begin of block active with frame title text-frb.
selection-screen begin of line.
parameters:
activ1 like rptxxxxx-kr_feld1 radiobutton group act default 'X'.
selection-screen comment 4(36) text-ta1.
selection-screen end of line.
selection-screen begin of line.
parameters:
activ2 like rptxxxxx-kr_feld1 radiobutton group act.
selection-screen comment 4(36) text-ta2.
selection-screen end of line.
selection-screen begin of line.
parameters:
activ3 like rptxxxxx-kr_feld1 radiobutton group act.
selection-screen comment 4(36) text-ta3.
selection-screen end of line.
selection-screen end of block active.

**********************************
* MODIFICATION                   *
**********************************
parameters: p_memid(30) type c.
**********************************

************************************************************************
*                     Macro definition                                 *
************************************************************************
*
define macro_it_check.
  if p&1_valid eq ' '.
    write pn-begda to error_begda.
    write pn-endda to error_endda.
    concatenate error_begda error_endda into error_message
                separated by space.
    perform error_handling using pernr-pernr '72' 'E' '111'
      &2 error_message space space.
    reject.
  endif.
end-of-definition.
*

initialization.
  pnptimed = 'M'.

start-of-selection.
  perform fill_fields_for_display_list.

* show active/inactive
  if activ1 = 'X'.                     "Rentner und Aktive, 2 und 3
    switch_active = 0.
    sw_active = ' '.
  elseif activ2 = 'X'.                 "Ruhende, Rentner und Aktive
    switch_active = 1.
    sw_active = ' '.
  else.
    switch_active = 1.        "Ausgetretene, Ruhende, Rentner und Aktive
    sw_active = '1'.
  endif.

* selection-begda might change
  report_begda = pn-begda.

get pernr.
  pro_end = 0.
  clear: psp, psp[].                                      "note 354871
* selection-beginn before hire date, pws from hire date
  rp-provide-from-frst p0001 ' ' pn-begda pn-endda.
  if pn-begda < p0001-begda. pn-begda = p0001-begda.endif.

*  rp_read_all_time_ity pn-begda pn-endda.                "XLTL9CK018334
  hlp_pn_endda = pn-endda + 1.         "XLTL9CK018334
  rp_read_all_time_ity pn-begda hlp_pn_endda.             "XLTL9CK018334


  perform build_psp.

  hd-pernr = pernr-pernr.
*
  provide * from p0001 * from p0002 between pn-begda and pn-endda.
* IT0001, IT0002 should be there all the time
    macro_it_check 0001 'Org. Zuordnung'(i01).
    macro_it_check 0002 'Daten zur Person'(i02).

    rp-set-name-format.
    rp-edit-name p0001 p0002 t001p-molga space.
    move $edit-name to hd-name.
*
    rp-read-t001p p0001-werks p0001-btrtl space.
    move-corresponding t001p to hd.
    move-corresponding hd to hd_sel.   "XLTL9CK018334
*
    pro_beg = pro_end + 1.
    pro_end = pro_beg + p0001-endda - p0001-begda.
* sw_active = '1': show active and inactive days from I0001-begda
* sw_active = ' ': show active days only.
* psp-active contains X for status 2 = 1,2,3 and  ' ' for status 2 = 0.
*
    l_mofid = hd-mofid.                        "NOTE604361
*
    loop at psp from pro_beg to pro_end
      where activ ne sw_active.
*
      call function 'HR_CHOOSE_SUBSTITUTION'
           exporting
                pernr     = pernr-pernr
                date      = psp-datum
                kug       = ' '
           tables
                i0001     = p0001
*           I0049     =
                i2003     = p2003
                i2003_exp = i2003
                .

      perform count_time_infotypes using psp-datum changing hd-menge.
      move-corresponding psp to hd.
*BEGIN XLTL9CK018334
      perform wochentag using hd-datum.
     perform ret246  using sy-langu wotnr             changing hd-kurzt.

     hd-mofid = l_mofid.                              "NOTE604361
     perform rethoct using sy-langu hd-mofid          changing hd-ftext.

     if hd-tagty = '0'. clear hd-tagty. endif.      "In Zukunft �ndern ?
     perform ret553t using sy-langu hd-tagty          changing hd-tatxt.

      if hd-tprog <> '****'.
        perform ret550s using sy-langu hd-motpr hd-tprog
                        changing hd-ttext.
      endif.

     perform ret551s using sy-langu hd-motpr hd-zmodn changing hd-ptext.
*
      single_line = '1'.
      loop at i2003 where tprog  is initial
                    and   schkz  is initial.
        single_line = '0'.
      endloop.
*
      if sy-tfill = 1 and i2003-vtken ne 'X'.
        single_line = '1'.
      endif.
*
      if single_line = '1'.            " nur einzeilige Anzeige.
*  TPROG <> '****' oder '****' und nur eine Vertretung, die am akt Tag
*                                                       beginnt
        read table i2003 index 1.
        if sy-subrc eq 0.
          if not i2003-mofid is initial.
            hd-mofid = i2003-mofid.
*           NOTE604361
            perform rethoct using sy-langu hd-mofid changing hd-ftext.
          endif.
          hd-vtart = i2003-vtart.
          perform ret556t using sy-langu hd-mover hd-vtart
                          changing hd-vtext.
        endif.
* DAYINT wegen AZPR
        read table dayint with key datum = psp-datum.
        if dayint-beguz is initial and dayint-enduz is initial.
          clear: hd-sobeg, hd-soend.
        else.
          if dayint-enduz gt '240000'.
            dayint-enduz = dayint-enduz + '0'.
          endif.
          write dayint-beguz to hd-sobeg using edit mask '__:__'.
          write dayint-enduz to hd-soend using edit mask '__:__'.
        endif.
        hd-inv_menge = hd-menge.
        append hd.
        clear: hd-vtart, hd-vtext,hd-ttext.
*
      else.
*     mehrzeilige Anzeige, mehrere Uhrzeitvertretungen, VTKEN
        move-corresponding hd to hd_vert.
        hd-inv_menge = hd-menge.
        append hd.
        clear hd.
*
        sort i2003 by begda.           " VTKEN nach hinten.
        loop at i2003.
          hd-vtart = i2003-vtart.
          perform ret556t using sy-langu hd_vert-mover hd-vtart
                         changing hd-vtext.


          if i2003-vtken eq 'X'.
            hd-datum = psp-datum + 1.
          else.
            hd-datum = psp-datum.
          endif.

          write i2003-beguz to hd-sobeg using edit mask '__:__'.
          write i2003-enduz to hd-soend using edit mask '__:__'.

          move-corresponding hd_vert to hd.
          append hd.
        endloop.
        move-corresponding hd_sel to hd.
      endif.                           " single line

*      hd-inv_menge = hd-menge.            "ALV copies only 20 columns
*      move-corresponding psp to hd.
*      read table dayint with key datum = psp-datum.
*      if dayint-beguz is initial and dayint-enduz is initial.
*        clear: hd-sobeg, hd-soend.
*      else.
*        if dayint-beguz gt '240000'.
*           dayint-beguz = dayint-beguz + '0'.
*        endif.
*        if dayint-enduz gt '240000'.
*          dayint-enduz = dayint-enduz + '0'.
*        endif.
*        write dayint-beguz to hd-sobeg using edit mask '__:__'.
*        write dayint-enduz to hd-soend using edit mask '__:__'.
*      endif.
**
*     loop at i2003 where begda le psp-datum
*              and         endda ge psp-datum.
*        if not i2003-mofid is initial.
*          hd-mofid = i2003-mofid.
*        endif.
*        hd-vtart = i2003-vtart.
*    perform ret556t using sy-langu hd-mover hd-vtart changing hd-vtext.
*     endloop.
**
*    perform wochentag.
*    perform ret246  using sy-langu wotnr             changing hd-kurzt.
*    perform rethoct using sy-langu hd-mofid          changing hd-ftext.
*
*    if hd-tagty = '0'. clear hd-tagty. endif.      "In Zukunft �ndern ?
*   perform ret553t using sy-langu hd-tagty          changing hd-tatxt.
*
*   perform ret550s using sy-langu hd-motpr hd-tprog changing hd-ttext.
*   perform ret551s using sy-langu hd-motpr hd-zmodn changing hd-ptext.
**
*      append hd.
*      clear: hd-vtart, hd-vtext.
*END XLTL9CK018334
    endloop.
  endprovide.                                               "PSP

  pn-begda = report_begda.


end-of-selection.

****************************************************************
* MODIFICATION                                                 *
* remove all display code and replace it with export to memory *
****************************************************************
export hd to memory id p_memid.
*  describe table hd lines entries.
*  call function 'HR_GET_ERROR_LIST'
*       TABLES
*            error      = ert
*            errortexts = errortexts
*       EXCEPTIONS
*            no_errors  = 1
*            others     = 2.
*
*  if entries eq 0 and sy-subrc eq 1.
**   nothing found to display
*    message  I050(PN).
*    exit.
*  endif.
*
** Presetting of RET_CD so that user always comes back to initial list
*  ret_cd = 1.
*  while ret_cd <> 0.
*    perform write_initial_list.
*    case ret_cd.
*      when '1'.                        "list daily work schedules
*        describe table hd_sel lines entries.
*        case entries.
*          when 0. message I805(PN).
*          when others.
*            perform list_TAZP.
*        endcase.
*      when '2'.                        "list I0007
*        describe table hd_sel lines entries.
*        case entries.
*          when 0.  message I805(PN).
*          when others.
*            perform show_0007.
*        endcase.
*      when '3'.                        "list Time infotype
*        describe table hd_sel lines entries.
*        case entries.
*          when 0.  message I805(PN).
*          when others.
*            perform list_200x.
*        endcase.
*    endcase.
*  endwhile.
****************************************************************

*
*----------------------------------------------------------------------
*  General forms
*----------------------------------------------------------------------
*
*----------------------------------------------------------------------
* Form fill_fields_for_display_list.
*----------------------------------------------------------------------
form fill_fields_for_display_list.
  define macro_fill_fields.
    clear fields.
    fields-co1 = &1.fields-co2 = &2.fields-co3 = &3.fields-co4 = &4.
    append fields.
  end-of-definition.

  define macro_fill_timefields.
    clear timefields.
    timefields-co1 = &1.timefields-co2 = &2.
    timefields-co3 = &3.timefields-co4 = &4.
    append timefields.
  end-of-definition.
  macro_fill_fields   space                    'PERNR' 'PERNR' 'F'.
  macro_fill_fields  'Name'(001)                space   space   'X'.
  macro_fill_fields   space                    'PAKEY' 'SEQNR'   'I'.
  macro_fill_fields   space                    'T001P' 'MOABW'   'I'.
  macro_fill_fields   space                    'T001P' 'MOVER'   'I'.
  macro_fill_fields  'Datum'(002)              'SYST'  'DATUM' space.
  macro_fill_fields  'Tag'(003)                'T246'  'KURZT' space.
  macro_fill_fields  'TAzp'(004)               'T550A' 'TPROG' space.
  macro_fill_fields  'TV'(005)                 'T550A' 'VARIA' space.
  macro_fill_fields  space                     'T550S' 'TTEXT' space.
  macro_fill_fields  'Va'(006)                 'T556'  'VTART' space.
  macro_fill_fields  space                     'T556T' 'VTEXT' space.
  macro_fill_fields  'Gp'(007)                 'T550A' 'MOTPR' space.
  macro_fill_fields  'Arb.B'(008)              space   space   space.
  macro_fill_fields  'Arb.E'(009)              space   space   space.
  macro_fill_fields  'S.Std'(010)         'PTEV_REP_H' 'STDAZ' space.
  macro_fill_fields  'Fk'(011)                 'THOL'  'KLASS' space.
  macro_fill_fields  'Tt'(012)                 'P2003' 'TAGTY' space.
  macro_fill_fields   space                    'T553T' 'LANGT' space.
  macro_fill_fields  'PAzp'(013)               'T551A' 'ZMODN' space.
  macro_fill_fields  space                     'T551S' 'ZTEXT' space.
  macro_fill_fields  'FKi'(014)                'T001P' 'MOFID' space.
  macro_fill_fields  space                     'THOCT' 'LTEXT' space.
  macro_fill_fields  'AZi'(015)           'PTEV_REP_H' 'ITANZ' space.
*
  macro_fill_timefields  space                 'PERNR' 'PERNR' 'F'.
  macro_fill_timefields  'Name'(001)            space   space   'X'.
  macro_fill_timefields  'Datum'(002)          'SYST'  'DATUM' space.
  macro_fill_timefields  'IT'(024)             'T582S' 'INFTY' space.
  macro_fill_timefields  space                 'T582S' 'ITEXT' space.
  macro_fill_timefields  'STyp'(020)           'PSKEY' 'SUBTY' space.
  macro_fill_timefields  'Subtyptext'(025)      space   space  space.
  macro_fill_timefields  'G�ltig ab'(026)      'PSKEY' 'BEGDA' space.
  macro_fill_timefields  'G�ltig bis'(027)     'PSKEY' 'ENDDA' space.
  macro_fill_timefields  'Beg.zt'(021)          space   space  space.
  macro_fill_timefields  'End.zt'(022)          space   space  space.
  macro_fill_timefields  'Dauer'(023)           space   space  space.
endform.

*----------------------------------------------------------------------*
*
* Generate reTxyz routines
*
*----------------------------------------------------------------------*
define macro_gen_form_retext3table.
*---------------------------------------------------------------------*
*       FORM re&1                                                     *
*---------------------------------------------------------------------*
*       ........                                                      *
*---------------------------------------------------------------------*
*  -->  RE_SPRSL                                                      *
*  -->  RE_MODIF                                                      *
*  -->  RE_SUBTY                                                      *
*  -->  RE_TEXT                                                       *
*---------------------------------------------------------------------*
form re&1 using  re_sprsl re_modif re_subty changing re_text.
  tables &1.
  if &1-&2 ne re_sprsl or &1-&3 ne re_modif or &1-&4 ne re_subty.
    select single * from &1 where &2 eq re_sprsl
                              and &3 eq re_modif
                              and &4 eq re_subty.
    if sy-subrc ne 0.
      &1-&2 = re_sprsl.&1-&3 = re_modif.&1-&4 = re_subty.
      concatenate &1-&2 &1-&3 &1-&4 into error_message.
      perform error_handling using pernr-pernr '72' 'E' &6
                                   error_message space space space.
      clear re_text. exit.
    endif.
  endif.
  re_text = &1-&5.
endform.
end-of-definition.

define macro_gen_form_retext2table.
*---------------------------------------------------------------------*
*       FORM re&1                                                     *
*---------------------------------------------------------------------*
*       ........                                                      *
*---------------------------------------------------------------------*
*  -->  RE_SPRSL                                                      *
*  -->  RE_MODIF                                                      *
*  -->  RE_TEXT                                                       *
*---------------------------------------------------------------------*
form re&1 using  re_sprsl re_modif  changing re_text.
  tables &1.
  if &1-&2 ne re_sprsl or &1-&3 ne re_modif.
    select single * from &1 where &2 eq re_sprsl and &3 eq re_modif.
    if sy-subrc ne 0.
      &1-&2 = re_sprsl. &1-&3 = re_modif.
      concatenate &1-&2 &1-&3 into error_message.
      perform error_handling using pernr-pernr '72' 'E' &5
                                   error_message space space space.
      clear re_text. exit.
    endif.
  endif.
  re_text = &1-&4.

endform.
end-of-definition.
macro_gen_form_retext3table t582S sprsl infty itbld itext '023'.
macro_gen_form_retext3table t554t sprsl moabw awart atext '010'.
macro_gen_form_retext3table t557t sprsl mover stnby stext '011'.
macro_gen_form_retext3table t556t sprsl mover vtart vText '014'.
macro_gen_form_retext3table t550S spras motpr tprog tText '022'.
macro_gen_form_retext3table t551s sprsl motpr zmodn ztext '039'.
macro_gen_form_retext2table thoct spras ident ltext '040'.
macro_gen_form_retext2table t246  sprsl wotnr kurzt '020'.
macro_gen_form_retext2table t553t sprsl tagty langt '008'.

*----------------------------------------------------------------------
*       FORM BUILD_PSP
*----------------------------------------------------------------------
form build_psp.
  call function 'HR_PERSONAL_WORK_SCHEDULE'
       exporting
            pernr             = pernr-pernr
            begda             = pn-begda
            endda             = pn-endda
*         KUG               =
*         REFRESH           = 'X'
*         WORKING_HOURS     = 'X'
          switch_activ      = switch_active

            i0001_i0007_error = '0'
            read_cluster     =   rdclust
*    IMPORTING
*         WARNING_OCCURED   =
       tables
           i0000             = p0000
           i0001             = p0001
           i0002             = p0002
           i0007             = p0007
*         I0049             =
           i2001             = p2001
           i2002             = p2002
           i2003             = p2003
            perws             = psp
       exceptions
            error_occured     = 1
            abort_occured     = 2
            others            = 3.
  if sy-subrc <> 0.
    call function 'HR_DISPLAY_ERROR_LIST'
         EXPORTING
              no_popup         = ' '
              no_print         = 'X'
              no_img           = ' '
         EXCEPTIONS
              invalid_linesize = 1
              others           = 2.
    if sy-subrc <> 0.
    endif.
    reject.
  endif.

  call function 'HR_WORK_SCHEDULE_TIMES'
       exporting
            pernr                   = pernr-pernr
            begda                   = pn-begda
            endda                   = pn-endda
*         KUG                     = ' '
*         BREAK_OVERTIME          = '1'
*         REFRESH_INFOTYPE_BUFFER = 'X'
*    IMPORTING
*         WARNING_OCCURED         =
       tables
           i0001                   = p0001
           i0007                   = p0007
           i2003                   = p2003
*         I0049                   =
            perws                   = psp
           daygen                  =  daygen
           dayint                  =  dayint
     exceptions
          error_occured           = 1
          perws_error             = 2
          others                  = 3
            .
  if sy-subrc <> 0.
    call function 'HR_DISPLAY_ERROR_LIST'
         EXPORTING
              no_popup         = ' '
              no_print         = 'X'
              no_img           = ' '
         EXCEPTIONS
              invalid_linesize = 1
              others           = 2.
    if sy-subrc <> 0.
    endif.
    reject.
  endif.
endform.
*---------------------------------------------------------------------*
*       FORM WOCHENTAG                                                *
*---------------------------------------------------------------------*
form wochentag
              using datum like psp-datum. "XLTL9CK018334
  data pack type p.
*pack = psp-datum mod 7.                     "XLTL9CK018334
  pack = datum mod 7.                  "XLTL9CK018334
  pack = pack + 6.
  wotnr = pack mod 7.
  if wotnr eq 0.
    wotnr = 7.
  endif.
endform.
*&---------------------------------------------------------------------*
*&      Form  count_time_infotypes
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
*      -->PSP_DATUM  text
*      <--counter  text
*----------------------------------------------------------------------*
form count_time_infotypes using    psp_datum
             changing counter like hd-menge.
  define macro_count_200x.
    loop at &1 where begda le psp_datum  and
                    endda ge psp_datum.
      counter  = counter + 1.
    endloop.
  end-of-definition.

  clear counter.

  describe table i2003 lines counter.  "XLTL9CK018334

  macro_count_200x p2001.
  macro_count_200x p2002.
* macro_count_200x i2003. "XLTL9CK018334
  macro_count_200x p2004.
  macro_count_200x p2005.

endform.                                                    "

*----------------------------------------------------------------------*
*       Form  ERROR_HANDLING
*----------------------------------------------------------------------*
*       Fuellen der Fehlertabelle                                      *
*----------------------------------------------------------------------*
FORM ERROR_HANDLING USING PERNR ARBGB typ NO MSGV1 MSGV2 MSGV3 MSGV4.
  data: l_pernr like p0001-pernr.                           "L9CK042157

  l_pernr = pernr.                                          "L9CK042157
  CALL FUNCTION 'HR_APPEND_ERROR_LIST'
       EXPORTING
*            PERNR = PERNR                                  "L9CK042157
            pernr = l_pernr                                 "L9CK042157
            ARBGB = arbgb
            MSGTY = typ
            MSGNO = NO
            MSGV1 = MSGV1
            MSGV2 = MSGV2
            MSGV3 = MSGV3
            MSGV4 = MSGV4.
ENDFORM.                               " ERROR_HANDLING
*----------------------------------------------------------------------
*       Output forms
*----------------------------------------------------------------------
*---------------------------------------------------------------------*
*       FORM WRITE_INITIAL_LIST                                       *
*---------------------------------------------------------------------*
*       Overview list per personell number                            *
*---------------------------------------------------------------------*
form write_initial_list.
  data: " header_line1(69), header_line2(69)," XLTL9CK002809
        header_begda(10), header_endda(10).
  write pn-begda to header_begda.
  write pn-endda to header_endda.
  if pn-begda = pn-endda.
    concatenate text-h01 header_begda into header_line1
                separated by space.
  else.
    concatenate text-h02 header_begda text-h03 header_endda
                into header_line1 separated by space.
  endif.
  clear sy-ucomm.
*XLTL9CK018484 Beginn
  call function 'HR_GET_ERROR_LIST'
       TABLES
            error      = ert
            errortexts = errortexts
       EXCEPTIONS
            no_errors  = 1
            others     = 2.
*XLTL9CK018484 End

  call function 'HR_DISPLAY_BASIC_LIST'
       EXPORTING
            basic_list_title     = 'Pers�nlicher Arbeitszeitplan'(h04)
            current_report       = 'RPTPSH10'
            list_level           = '01'
            file_name            = 'RPTPSH10'
            head_line1           = header_line1
            lay_out              = 5
            dyn_pushbutton_text1 = 'TagesAZP'(p01)
            dyn_pushbutton_text2 = 'Sollarbeitszeit'(p02)
            dyn_pushbutton_text3 = 'Zeitinfotypen'(p03)
            alv_marker           = 'ALVMARKER'
       IMPORTING
            return_code          = ret_cd
       TABLES
            data_tab             = hd
            fieldname_tab        = fields
            select_tab           = hd_sel
            error_tab            = ert
       EXCEPTIONS
            download_problem     = 1
            no_data_tab_entries  = 2
            others               = 3.
  case sy-subrc.
    when 0.
    when 1.
      CALL FUNCTION 'HR_APPEND_ERROR_LIST'
           EXPORTING
                ARBGB = 'PN'
                MSGTY = 'I'
                MSGNO = '173'.         "PC - Download nicht m�glich.
    when others.
      CALL FUNCTION 'HR_APPEND_ERROR_LIST'
           EXPORTING
                ARBGB = 'PN'
                MSGTY = 'E'
                MSGNO = '800'.         "Interner Fehler!

      call function 'HR_DISPLAY_ERROR_LIST'
           EXPORTING
                no_popup = ' '
                no_print = 'X'
                no_img   = ' '
           EXCEPTIONS
                others   = 1.
      if sy-subrc <> 0.
      endif.
      exit.
  endcase.
endform.

*---------------------------------------------------------------------*
*       FORM WRITE_INFOTYPE_LIST                                      *
*---------------------------------------------------------------------*
*       List of all time-infotype records for selected employee       *
*---------------------------------------------------------------------*
form write_infotype_list  changing ret_cd2 like sy-subrc.

  data push_button_text  like smp_dyntxt.

  push_button_text-icon_id =  icon_select_detail.
  push_button_text-quickinfo = 'Detail ausw�hlen'(p04).

  clear sy-ucomm.
  call function 'HR_DISPLAY_BASIC_LIST'
       EXPORTING
            basic_list_title     = 'Anzeige von Zeitinfotypen'(h05)
            current_report       = 'RPTPSH10_200X'
            list_level           = '02'
            file_name            = 'RPTPSH10_200X'
            head_line1           = header_line1  "XLTL9CK002809
            lay_out              = 5
            dyn_pushbutton_text1 = push_button_text
       IMPORTING
            return_code          = ret_cd2
       TABLES
            data_tab             = i200x
            fieldname_tab        = timefields
            select_tab           = i200x_sel
       EXCEPTIONS
            download_problem     = 1
            no_data_tab_entries  = 2
            others               = 3.
  case sy-subrc.
    when 0.
    when 1.
      CALL FUNCTION 'HR_APPEND_ERROR_LIST'
           EXPORTING
                ARBGB = 'PN'
                MSGTY = 'I'
                MSGNO = '173'.         "PC - Download nicht m�glich.
    when others.
      CALL FUNCTION 'HR_APPEND_ERROR_LIST'
           EXPORTING
                ARBGB = 'PN'
                MSGTY = 'W'
                MSGNO = '800'.
  endcase.
endform.
*&---------------------------------------------------------------------*
*&      Form  show_0007
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
*  -->  p1        text
*  <--  p2        text
*----------------------------------------------------------------------*
FORM show_0007.
  data: begin of date_0007 occurs 0,
         datum like psp-datum,
        end of date_0007.

  data:beg_0007 like pn-begda,
       end_0007 like pn-endda.

  loop at hd_sel.
    move hd_sel-datum to date_0007.
    append date_0007.
    at end of pernr.
      sort date_0007.
      describe table date_0007 lines entries.
      read table date_0007 index 1.
      beg_0007 = date_0007-datum.
      read table date_0007 index entries.
      end_0007 = date_0007-datum.
      rp_read_infotype hd_sel-pernr 0007 P0007 beg_0007 end_0007.
      describe table p0007 lines entries.
      case entries.
        when 0.
          write beg_0007 to error_begda.
          write end_0007 to error_endda.
          concatenate error_begda error_endda into error_message
              separated by space.
          perform error_handling using hd_sel-pernr '72' 'E' '111'
          '0007' error_message space space.
        when 1.
          set parameter id 'PER' field hd_sel-pernr.
          set parameter id 'ITP' field '0007'.
          set parameter id 'BEG' field beg_0007.
          set parameter id 'END' field end_0007.
          set parameter id 'FCD' field 'DIS'.
          call transaction 'PA20' and skip first screen.
        when others.
          set parameter id 'PER' field hd_sel-pernr.
          set parameter id 'ITP' field '0007'.
          set parameter id 'BEG' field beg_0007.
          set parameter id 'END' field end_0007.
          set parameter id 'FCD' field 'LIST'.
          call transaction 'PA20' and skip first screen.
      endcase.
      refresh date_0007.
    endat.
  endloop.
ENDFORM.                               " show_0007

*&---------------------------------------------------------------------*
*&      Form  list_200x
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
*  -->  p1        text
*  <--  p2        text
*----------------------------------------------------------------------*
FORM list_200x.
* Tabelle zur �bergabe der Zeitinfotypen an HR_DISPLAY_BASIC_LIST
  data: ret_cd2 like sy-subrc.
  data: i200x_entries type i.

  data: ldatum like hd_sel-datum.      "XLTL9CK018334

  ldatum = hd_sel-datum + '1'.         "XLTL9CK018334

  clear i200x.
  refresh i200x.
  loop at hd_sel where inv_menge ne '0'.
*             Infotypen zum Satz vorhanden
    pernr-pernr = hd_sel-pernr.
*   rp_read_all_time_ity hd_sel-datum hd_sel-datum. "XLTL9CK018334
    rp_read_all_time_ity hd_sel-datum ldatum. "XLTL9CK018334
*
    call function 'HR_CHOOSE_SUBSTITUTION'
         exporting
              pernr     = hd_sel-pernr
              date      = hd_sel-datum
              kug       = ' '
         tables
              i0001     = p0001
*           I0049     =
              i2003     = p2003
              i2003_exp = i2003
              .
    sort i2003 by begda. "XLTL9CK018334
    rp_read_all_time_ity hd_sel-datum hd_sel-datum. "XLTL9CK018334

   perform fill_i200x.
  endloop.                             "loop for all entries of HD_SEL
  describe table i200x lines i200x_entries.
  case i200x_entries.
    when 0.
*            lines selected with no time-it available
      message I122(72).
    when others.
* Presetting of RET_CD2 for list of time-infotype records
      ret_cd2 = 1.
      while ret_cd2 <> 0.
        perform write_infotype_list changing ret_cd2.
        case ret_cd2.
          when '1'.                    "P200x record
            describe table i200x_sel lines i200x_entries.
            case i200x_entries.
              when 0. message I805(PN).
              when others.
                set parameter id 'PER' field i200x_sel-pernr.
                set parameter id 'ITP' field i200x_sel-infty.
                set parameter id 'SUB' field i200x_sel-subty.
                set parameter id 'BEG' field i200x_sel-begda.
                set parameter id 'END' field i200x_sel-endda.
                set parameter id 'FCD' field 'DIS'.
                call transaction 'PA51' and skip first screen.
            endcase.
        endcase.
      endwhile.                        "show time-it list
  endcase.                                                  "
ENDFORM.                               " list_200x

*&---------------------------------------------------------------------*
*&      Form  list_TAZP
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
*  -->  p1        text
*  <--  p2        text
*----------------------------------------------------------------------*
FORM list_TAZP.
*XLTL9CK018484 Fehlerhandling Korrektur
  loop at hd_sel where tprog = '****'
                 or    tprog is initial.                   "note 322021
*           Keine Anzeige von TagesAZP, da TagesAZP = '****'
    perform error_handling using hd_sel-pernr '72' 'E' '121'
    space space space space.
    exit.
  endloop.
  perform fill_dba_sellist_cluster.


  if not dba_sellist_cluster[] is initial.

    call function 'VIEWCLUSTER_MAINTENANCE_CALL'
         EXPORTING
              viewcluster_name    = 'T550A'
              maintenance_action  = 'S'
         TABLES
              DBA_SELLIST_CLUSTER = DBA_SELLIST_CLUSTER
         EXCEPTIONS
              no_show_auth        = 2
              others              = 1.
    case sy-subrc.
      when '1'.
        perform error_handling using space 'PN' 'E' '800'
        space space space space.
      when '2'.
        perform error_handling using space 'P2' 'I' '759'
        'T550A' space space space.     "Keine Berechtigung zum Anzeigen
    endcase.

  endif.

ENDFORM.                               " list_TAZP
*----------------------------------------------------------------------
*       Fill table forms
*----------------------------------------------------------------------
*
*&---------------------------------------------------------------------*
*&      Form  fill_i200x
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
*  -->  p1        text
*  <--  p2        text
*----------------------------------------------------------------------*
form fill_i200x.
  define macro_fill_i200x.

    loop at &1 where begda le pn-endda
                  and   endda ge pn-begda.
      move-corresponding &1 to i200x.
      write &1-beguz to i200x-beguz using edit mask '__:__'.
      write &1-enduz to i200x-enduz  using edit mask '__:__'.
      i200x-pernr = hd_sel-pernr.
      i200x-name  = hd_sel-name.
      perform ret582s using sy-langu  '&2' space changing i200x-itext.
      perform re&3    using sy-langu   &4  &5    changing i200x-atext.
      write &6 to i200x-stdaz no-zero right-justified.
      append i200x.
      clear i200x.
    endloop.
  end-of-definition.

  i200x-datum = hd_sel-datum.
 macro_fill_i200x p2001 2001 t554t hd_sel-moabw p2001-awart p2001-stdaz.
 macro_fill_i200x p2002 2002 t554t hd_sel-moabw p2002-awart p2002-stdaz.
  macro_fill_i200x i2003 2003 t556t hd_sel-mover i2003-vtart ' '.
  macro_fill_i200x p2004 2004 t557t hd_sel-mover p2004-stnby ' '.
 macro_fill_i200x p2005 2005 mehr  space        space       p2005-stdaz.
endform.                               " fill_i200x
*----------------------------------------------------------------------*
*
*----------------------------------------------------------------------*
form remehr using d1 type c d2 type c d3 type c changing d4 type c.
endform.
*&---------------------------------------------------------------------*
*&      Form  fill_dba_sellist_cluster
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
*  -->  p1        text
*  <--  p2        text
*----------------------------------------------------------------------*
FORM fill_dba_sellist_cluster.
  data:      550a like vimsellist occurs 0 with header line,
             550p like vimsellist occurs 0 with header line,
             550x like vimsellist occurs 0 with header line.

  define macro_dba_sellist_cluster_flds.
    clear dba_sellist_cluster.
    DBA_SELLIST_CLUSTER-OBJECT    = &1.
    DBA_SELLIST_CLUSTER-sellist[] = &2.
    append dba_sellist_cluster.
  end-of-definition.

  refresh: 550a, 550p, 550x, dba_sellist_cluster.

  loop at hd_sel where tprog ne '****'
                 and  not tprog is initial. "XLTL9CK018334
    perform fill_arg_t550apx tables 550a 550p 550x.
  endloop.

  if not 550a is initial.              "XLTL9CK018334
    macro_dba_sellist_cluster_flds 'V_T550A' 550A[].
    macro_dba_sellist_cluster_flds 'V_T550P' 550P[].
    macro_dba_sellist_cluster_flds 'V_T550X' 550X[].
  endif.                               "XLTL9CK018334

ENDFORM.                               " fill_dba_sellist_cluster

*&---------------------------------------------------------------------*
*&      Form  fill_arg_t550apx
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
*  -->  p1        text
*  <--  p2        text
*----------------------------------------------------------------------*
FORM fill_arg_t550apx tables a_sellist structure VIMSELLIST
                             p_sellist structure VIMSELLIST
                             x_sellist structure VIMSELLIST .

  DATA: datum_vmc(10),
        recno like t550x-recno value '01',
        seqno like t550a-seqno.

  select single * from t550a where motpr eq hd_sel-motpr
                             and tprog eq hd_sel-tprog
                             and varia eq hd_sel-varia
                             and endda ge hd_sel-datum
                             and begda le hd_sel-datum.

  if sy-subrc ne 0.
  concatenate hd_sel-tprog hd_sel-varia hd_sel-datum into error_message.
    PERFORM ERROR_HANDLING USING space
         '72' 'E' '009' error_message space space space.
  endif.
  write t550a-endda to datum_vmc.

  perform ini_fld tables a_sellist using 'MOTPR' 'EQ' t550a-motpr 'OR'.
  perform ini_fld tables a_sellist using 'VARIA' 'EQ' t550a-varia 'AND'.
  perform ini_fld tables a_sellist using 'TPROG' 'EQ' t550a-tprog 'AND'.
  perform ini_fld tables a_sellist using 'SEQNO' 'EQ' t550a-seqno 'AND'.
  perform ini_fld tables a_sellist using 'ENDDA' 'EQ' datum_vmc   'AND'.

  select max( seqno ) into (seqno)
        from t550p where motpr eq hd_sel-motpr
                   and   pamod eq t550a-pamod.

  perform ini_fld tables p_sellist using 'MOTPR' 'EQ' t550a-motpr 'OR'.
  perform ini_fld tables p_sellist using 'PAMOD' 'EQ' t550a-pamod 'AND'.
  perform ini_fld tables p_sellist using 'SEQNO' 'LE' seqno       'AND'.

  select max( seqno )  into (seqno)
         from t550x where regel eq t550a-regel
                    and recno eq recno.

  perform ini_fld tables x_sellist using 'RECNO' 'LE' recno       'OR'.
  perform ini_fld tables x_sellist using 'REGEL' 'EQ' t550a-regel 'AND'.
  perform ini_fld tables x_sellist using 'SEQNO' 'LE' seqno       'AND'.

ENDFORM.                               " fill_arg_t550apx

*---------------------------------------------------------------------*
*       FORM INIT_FIELD                                               *
*---------------------------------------------------------------------*
form ini_fld tables dba_sellist structure VIMSELLIST
                 using fldna
                       fldop
                       fldva and_or.

  data: tabix like sy-tabix.

  describe table dba_sellist lines tabix.
  if tabix gt 0.
    read table dba_sellist index tabix.
    dba_sellist-and_or = and_or.
    modify dba_sellist index tabix.
  endif.
  clear dba_sellist.
  dba_sellist-viewfield = fldna.
  dba_sellist-operator = fldop.
  dba_sellist-value = fldva.
  append dba_sellist.
endform.



comments powered by Disqus