abap开发中获取批次特性值的两种方式

这里就获取批次特性值的两种方式(1.函数: BAPI_OBJCL_GETDETAIL  2.取表)以及各自需要的时间,开发一个时间比对程序,以方便在项目或日常开发中选择适合各自系统的方式

由于之前是S/4的版本,现在用ECC开发很多语法不习惯,所以如果各位大姑看到有不好的写法,还请见谅,也可以各自进一步优化,下面展示代码:

*&---------------------------------------------------------------------*
*& Report  ZTEXT_GET_CHARG
*&
*&---------------------------------------------------------------------*
*&
*& 分别测试通过函数和取表的方式获取批次特性值的时间
*&---------------------------------------------------------------------*

report ztext_get_charg.

include ztext_get_charg_top.

include ztext_get_charg_screen.

include ztext_get_charg_f01.

initialization.

at selection-screen.

at selection-screen output.
  perform frm_modify_screen.

start-of-selection.

 perform frm_get_data.

  if p_fun = 'X'.

    perform frm_get_from_function.

  elseif p_table = 'X'.

    perform frm_get_from_table.

  endif.

end-of-selection.

  perform frm_display_alv.

​

*&---------------------------------------------------------------------*
*&  包含                ZTEXT_GET_CHARG_TOP
*&---------------------------------------------------------------------*
 tables:mara,mch1,mchb.

 types:begin of zcharg,
     matnr           type mara-matnr,
     charg           type mch1-charg,
     werks           type mchb-werks,
     time            type timestampl,
     z_xp_led_std_iv type char33,
     z_xp_led_std_wd type char33,
     z_xp_led_std_vf type char33,
     z_ty_led_bin    type char30,
     z_xp_led_r_iv   type char33,
     z_xp_led_r_wd   type char33,
     objek           type inob-objek,
     end of zcharg.


types:begin of ty_s_ausp,
    objek type inob-objek,
    atinn type ausp-atinn,
    atwrt type ausp-atwrt,
    atflv type ausp-atflv,
    atflb type ausp-atflb,
  end of ty_s_ausp,

  ty_t_ausp type standard table of ty_s_ausp
              with non-unique sorted key ns01
              components objek
                         atinn.

 data:  gt_ausp type  ty_t_ausp,
        gs_ausp like line of  gt_ausp.

 data:gt_zcharg type table of zcharg,
      gs_zcharg type zcharg.

 field-symbols: <fs_zcharg> like line of gt_zcharg.

 data:
gs_layout1      type lvc_s_layo,
pv_col_pos      type     i value 1,
gv_repid    type syrepid,
gs_fieldcat type lvc_s_fcat,
gt_fieldcat type lvc_t_fcat.

 data:gv_time_beg type timestampl,gv_time_end type timestampl,
      gv_comp_tim type timestampl.

*&---------------------------------------------------------------------*
*&  包含                ZTEXT_GET_CHARG_SCREEN
*&---------------------------------------------------------------------*

    selection-screen begin of block bk1  with frame title text-t01.
    select-options:
    s_matnr for mara-matnr modif id md1,
    s_charg for mch1-charg modif id md1.



    parameters:
     p_werks        like  mchb-werks modif id md2,
     p_fun          radiobutton group g1 default 'X'user-command cm1,
     p_table        radiobutton group g1.

    selection-screen end of block bk1.
*&---------------------------------------------------------------------*
*&  包含                ZTEXT_GET_CHARG_F01
*&---------------------------------------------------------------------*
*&---------------------------------------------------------------------*
*&      Form  FRM_MODIFY_SCREEN
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
*  -->  p1        text
*  <--  p2        text
*----------------------------------------------------------------------*
form frm_modify_screen .
  loop at screen.
    if screen-group1 = 'MD1'.
      screen-required = 2.
      screen-invisible = '0'.
      screen-active = 1.
    endif.

    case 'X'.
      when p_fun .
        if screen-group1 = 'MD2'.
          screen-required = 0.
          screen-invisible = '1'.
          screen-active = 0.
        endif.
      when p_table.
        if screen-group1 = 'MD2'.
          screen-required = 0.
          screen-invisible = '0'.
          screen-active = 1.
        endif.
      when others.
    endcase.

    modify screen.
  endloop.
endform.                    " FRM_MODIFY_SCREEN

*&---------------------------------------------------------------------*
*&      Form  FRM_GET_DATA
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
*  -->  p1        text
*  <--  p2        text
*----------------------------------------------------------------------*
form frm_get_data .

  select
      mch1~matnr
      mch1~charg
      mchb~werks
 into corresponding fields of table gt_zcharg
 from mch1
 inner join mchb on mch1~matnr = mchb~matnr and mch1~charg = mchb~charg
 where mch1~matnr in s_matnr
   and mch1~charg in s_charg.

endform.                    " FRM_GET_DATA

*&---------------------------------------------------------------------*
*&      Form  FRM_GET_FROM_FUNCTION
*&---------------------------------------------------------------------*
*       text  用函数获取批次特性值
*----------------------------------------------------------------------*
*  -->  p1        text
*  <--  p2        text
*----------------------------------------------------------------------*
form frm_get_from_function .

  data:lt_return type table of bapiret2 with header line,
       lt_allocvaluesnum  type table of bapi1003_alloc_values_num,
       lt_allocvalueschar type table of bapi1003_alloc_values_char,
       lt_allocvaluescurr type table of bapi1003_alloc_values_curr,
       ls_allocvaluesnum  type  bapi1003_alloc_values_num,
       ls_allocvalueschar type  bapi1003_alloc_values_char,
       ls_allocvaluescurr type  bapi1003_alloc_values_curr.
  data:
       lv_object_long like bapi1003_key-object,
       lv_classnum  like bapi1003_key-classnum,
       lv_classtype  like bapi1003_key-classtype,
       lv_objecttable type tabelle,
       lv_objectkey type bapi1003_key-object.

  clear:gv_time_beg,gv_time_end ,gv_comp_tim.

  get time stamp field gv_time_beg.

  loop at gt_zcharg assigning <fs_zcharg>.
    "获取批次特性
    if <fs_zcharg>-matnr  is not initial and <fs_zcharg>-charg is not initial.

      call function 'VB_BATCH_2_CLASS_OBJECT'   "获取批次的分类信息
        exporting
          i_matnr = <fs_zcharg>-matnr  "物料号
          i_charg = <fs_zcharg>-charg  "批次号
          i_werks = <fs_zcharg>-werks  "工厂
        importing
          e_objek = lv_object_long
          e_obtab = lv_objecttable
          e_klart = lv_classtype
          e_class = lv_classnum.

      lv_objectkey  =  lv_object_long.

      call function 'BAPI_OBJCL_GETDETAIL'   "获取批次的分类特性值
        exporting
          objectkey       = lv_objectkey
          objecttable     = lv_objecttable
          classnum        = lv_classnum
          classtype       = lv_classtype
*       KEYDATE         = SY-DATUM
*       UNVALUATED_CHARS       = ' '
*       LANGUAGE        = SY-LANGU
*          objectkey_long  = lv_object_long
* IMPORTING
*       STATUS          =
*       STANDARDCLASS   =
        tables
          allocvaluesnum  = lt_allocvaluesnum
          allocvalueschar = lt_allocvalueschar     "中的特征值名称和特征值对应于表中的各字段和其值
          allocvaluescurr = lt_allocvaluescurr
          return          = lt_return.

      read table lt_allocvalueschar into ls_allocvalueschar index 1.
      if  sy-subrc = 0 and ls_allocvalueschar-charact =  'Z_TY_LED_BIN'.          "通用特性供应商BIN号   0000001041
        <fs_zcharg>-z_ty_led_bin     = ls_allocvalueschar-value_char.
      endif.

      loop at lt_allocvaluesnum into ls_allocvaluesnum.
        case ls_allocvaluesnum-charact.
          when  'Z_XP_LED_STD_IV'.                          "0000001026
            <fs_zcharg>-z_xp_led_std_iv  = ls_allocvaluesnum-value_from && '-' && ls_allocvaluesnum-value_to.
          when   'Z_XP_LED_STD_WD'.                         "0000001027
            <fs_zcharg>-z_xp_led_std_wd  = ls_allocvaluesnum-value_from && '-' && ls_allocvaluesnum-value_to.
          when   'Z_XP_LED_STD_VF'.                         "0000001028
            <fs_zcharg>-z_xp_led_std_vf  = ls_allocvaluesnum-value_from && '-' && ls_allocvaluesnum-value_to.
          when 'Z_XP_LED_R_IV'.             " 0000001029
            <fs_zcharg>-z_xp_led_r_iv    = ls_allocvaluesnum-value_from && '-' && ls_allocvaluesnum-value_to.
          when 'Z_XP_LED_R_WD'.                             "0000001030
            <fs_zcharg>-z_xp_led_r_wd    = ls_allocvaluesnum-value_from && '-' && ls_allocvaluesnum-value_to.
          when others.
        endcase.

      endloop.

    endif.
  endloop.

  get time stamp field gv_time_end.
  gv_comp_tim = ( gv_time_end - gv_time_beg ) * 1000.

*  CLEAR:<fs_zcharg>.

  loop at gt_zcharg assigning <fs_zcharg> .
    <fs_zcharg>-time = gv_comp_tim.
  endloop.

endform.                    " FRM_GET_FROM_FUNCTION

*&---------------------------------------------------------------------*
*&      Form  FRM_GET_FROM_TABLE
*&---------------------------------------------------------------------*
*       text  从表中获取批次特性值
*----------------------------------------------------------------------*
*  -->  p1        text
*  <--  p2        text
*----------------------------------------------------------------------*
form frm_get_from_table .
  data:lv_cuobj type ausp-objek.
  clear:gv_time_beg,gv_time_end ,gv_comp_tim .
  get time stamp field gv_time_beg.

  loop at gt_zcharg assigning <fs_zcharg> .
    clear lv_cuobj.
    lv_cuobj+0(18)   = <fs_zcharg>-matnr.
    lv_cuobj+18(10)  = <fs_zcharg>-charg.
    <fs_zcharg>-objek   = lv_cuobj.
  endloop.

  "取批次特性
  if gt_zcharg is not initial.

    select
      inob~objek
      ausp~atinn
      ausp~atwrt
      ausp~atflv
      ausp~atflb
    into corresponding fields of table gt_ausp
    from  ausp
    inner join inob on inob~cuobj = ausp~objek
    for all entries in gt_zcharg
    where  inob~obtab  = 'MCH1'
      and  inob~objek = gt_zcharg-objek
      and ( ausp~atinn = '1026'
       or   ausp~atinn = '1027'
       or   ausp~atinn = '1028'
       or   ausp~atinn = '1029'
       or   ausp~atinn = '1030'
       or   ausp~atinn = '1041' ).

  endif.

*  CLEAR:<fs_zcharg>.
  loop at gt_zcharg assigning <fs_zcharg> .

    clear:gs_ausp.
    read table gt_ausp into gs_ausp with key ns01
     components objek = <fs_zcharg>-objek+0(28)
                atinn = '1026'.
    if sy-subrc = 0.
      call function 'QSS0_FLTP_TO_CHAR_CONVERSION'
        exporting
          i_number_of_digits       = 2
          i_fltp_value             = gs_ausp-atflv
          i_value_not_initial_flag = 'X'
          i_screen_fieldlength     = 16
        importing
          e_char_field             = <fs_zcharg>-z_xp_led_std_iv+0(16).

*      <fs_zcharg>-z_xp_led_std_iv+16(1) = '-' .

      call function 'QSS0_FLTP_TO_CHAR_CONVERSION'
        exporting
          i_number_of_digits       = 2
          i_fltp_value             = gs_ausp-atflb
          i_value_not_initial_flag = 'X'
          i_screen_fieldlength     = 16
        importing
          e_char_field             = <fs_zcharg>-z_xp_led_std_iv+16(16).
    endif.

    clear:gs_ausp.
    read table gt_ausp into gs_ausp with key ns01
     components objek = <fs_zcharg>-objek+0(28)
                atinn = '1027'.
    if sy-subrc = 0.
      call function 'QSS0_FLTP_TO_CHAR_CONVERSION'
        exporting
          i_number_of_digits       = 2
          i_fltp_value             = gs_ausp-atflv
          i_value_not_initial_flag = 'X'
          i_screen_fieldlength     = 16
        importing
          e_char_field             = <fs_zcharg>-z_xp_led_std_wd+0(16).

*      <fs_zcharg>-z_xp_led_std_wd+16(1) = '-' .

      call function 'QSS0_FLTP_TO_CHAR_CONVERSION'
        exporting
          i_number_of_digits       = 2
          i_fltp_value             = gs_ausp-atflb
          i_value_not_initial_flag = 'X'
          i_screen_fieldlength     = 16
        importing
          e_char_field             = <fs_zcharg>-z_xp_led_std_wd+16(16).

    endif.

    clear:gs_ausp.
    read table gt_ausp into gs_ausp with key ns01
     components objek = <fs_zcharg>-objek+0(28)
                atinn = '1028'.
    if sy-subrc = 0.
      call function 'QSS0_FLTP_TO_CHAR_CONVERSION'
        exporting
          i_number_of_digits       = 2
          i_fltp_value             = gs_ausp-atflv
          i_value_not_initial_flag = 'X'
          i_screen_fieldlength     = 16
        importing
          e_char_field             = <fs_zcharg>-z_xp_led_std_vf+0(16).

*      <fs_zcharg>-z_xp_led_std_vf+16(1) = '-' .

      call function 'QSS0_FLTP_TO_CHAR_CONVERSION'
        exporting
          i_number_of_digits       = 2
          i_fltp_value             = gs_ausp-atflb
          i_value_not_initial_flag = 'X'
          i_screen_fieldlength     = 16
        importing
          e_char_field             = <fs_zcharg>-z_xp_led_std_vf+16(16).
    endif.

    clear:gs_ausp.
    read table gt_ausp into gs_ausp with key ns01
     components objek = <fs_zcharg>-objek+0(28)
                atinn = '1029'.
    if sy-subrc = 0.
      call function 'QSS0_FLTP_TO_CHAR_CONVERSION'
        exporting
          i_number_of_digits       = 2
          i_fltp_value             = gs_ausp-atflv
          i_value_not_initial_flag = 'X'
          i_screen_fieldlength     = 16
        importing
          e_char_field             = <fs_zcharg>-z_xp_led_r_iv+0(16).
*      <fs_zcharg>-z_xp_led_r_iv+16(1) = '-' .

      call function 'QSS0_FLTP_TO_CHAR_CONVERSION'
        exporting
          i_number_of_digits       = 2
          i_fltp_value             = gs_ausp-atflb
          i_value_not_initial_flag = 'X'
          i_screen_fieldlength     = 16
        importing
          e_char_field             = <fs_zcharg>-z_xp_led_r_iv+16(16).
    endif.

    clear:gs_ausp.
    read table gt_ausp into gs_ausp with key ns01
     components objek = <fs_zcharg>-objek+0(28)
                atinn = '1030'.
    if sy-subrc = 0.
      call function 'QSS0_FLTP_TO_CHAR_CONVERSION'
        exporting
          i_number_of_digits       = 2
          i_fltp_value             = gs_ausp-atflv
          i_value_not_initial_flag = 'X'
          i_screen_fieldlength     = 16
        importing
          e_char_field             = <fs_zcharg>-z_xp_led_r_wd+0(16).

*      <fs_zcharg>-z_xp_led_r_wd+16(1) = '-' .

      call function 'QSS0_FLTP_TO_CHAR_CONVERSION'
        exporting
          i_number_of_digits       = 2
          i_fltp_value             = gs_ausp-atflb
          i_value_not_initial_flag = 'X'
          i_screen_fieldlength     = 16
        importing
          e_char_field             = <fs_zcharg>-z_xp_led_r_wd+16(16).
    endif.

    "通用特性供应商BIN号
    clear:gs_ausp.
    read table gt_ausp into gs_ausp with key ns01
     components objek = <fs_zcharg>-objek+0(28)
                atinn = '1041'.
    if sy-subrc = 0.
      <fs_zcharg>-z_ty_led_bin = gs_ausp-atwrt.
    endif.

  endloop.

  get time stamp field gv_time_end.
  gv_comp_tim = ( gv_time_end - gv_time_beg ) * 1000.

  loop at gt_zcharg assigning <fs_zcharg> .
    <fs_zcharg>-time = gv_comp_tim.
  endloop.

endform.                    " FRM_GET_FROM_TABLE
*&---------------------------------------------------------------------*
*&      Form  FRM_DISPLAY_ALV
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
*  -->  p1        text
*  <--  p2        text
*----------------------------------------------------------------------*
form frm_display_alv .
  data ls_variant type disvariant.
  data ls_layout  type lvc_s_layo.

  gv_repid = sy-repid.

  ls_variant-report = sy-repid.
  ls_variant-handle = '1'.

* LAYOUT
  ls_layout-cwidth_opt = abap_true.
  ls_layout-zebra      = abap_true.
  ls_layout-sel_mode   = 'A'.


  perform frm_append_col.

* CALL function module SHOW ALV
  call function 'REUSE_ALV_GRID_DISPLAY_LVC'
    exporting
      i_callback_program       = gv_repid
      i_callback_pf_status_set = 'FRM_SET_STATUS'
*     I_CALLBACK_USER_COMMAND  = 'FRM_ALV_COMMAND'
      it_fieldcat_lvc          = gt_fieldcat[]
      is_layout_lvc            = ls_layout
      i_save                   = 'A'
      is_variant               = ls_variant
    tables
      t_outtab                 = gt_zcharg
    exceptions
      program_error            = 1
      others                   = 2.
  if sy-subrc <> 0.
  else.
  endif.
endform.                    " FRM_DISPLAY_ALV
*&---------------------------------------------------------------------*
*&      Form  FRM_APPEND_COL
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
*  -->  p1        text
*  <--  p2        text
*----------------------------------------------------------------------*
form frm_append_col .
  define mcr_fieldcat.

    clear gs_fieldcat.
    gs_fieldcat-fieldname  = &1.
    gs_fieldcat-coltext    =
    gs_fieldcat-scrtext_l  =
    gs_fieldcat-scrtext_m  =
    gs_fieldcat-scrtext_s  =
    gs_fieldcat-reptext    = &2.
    gs_fieldcat-key        = &3.
    gs_fieldcat-edit       = &4.
    gs_fieldcat-ref_table  = &5.
    gs_fieldcat-ref_field  = &6.
    append gs_fieldcat to gt_fieldcat.

  end-of-definition.

  refresh gt_fieldcat.

  mcr_fieldcat:
    'MATNR'             text-001  ''  '' 'MARA' 'MATNR', "物料号
    'CHARG'             text-002  ''  '' 'MCHB' 'CHARG', "批次
    'TIME'              text-005  ''  '' 'BPTC01' 'TIMESTAMPL', "时间
    'Z_XP_LED_STD_IV'   text-007  ''  '' 'AUSP' 'ATWRT', "批次特性
    'Z_XP_LED_STD_WD'   text-008  ''  '' 'AUSP' 'ATFLV', "批次特性
    'Z_XP_LED_STD_VF'   text-009  ''  '' 'AUSP' 'ATFLV', "批次特性
    'Z_TY_LED_BIN'      text-006  ''  '' 'AUSP' 'ATFLV', "批次特性
    'Z_XP_LED_R_IV'     text-010  ''  '' 'AUSP' 'ATFLV', "批次特性
    'Z_XP_LED_R_WD'     text-011  ''  '' 'AUSP' 'ATFLV'. "批次特性
*    'Z_XP_LED_STD_VF'   text-012  ''  '' 'AUSP' 'ATFLV'. "批次特性


endform.                    " FRM_APPEND_COL

*&---------------------------------------------------------------------*
*& Form st
*&---------------------------------------------------------------------*
* -->RT_EXTAB text
*----------------------------------------------------------------------*
form frm_set_status using rt_extab type slis_t_extab. "状态栏/工具栏
  set pf-status 'ST_0001' excluding rt_extab.
endform. "st

由于函数取数慢的点在于批次特性值比较多的情况,在选择测试数据时可以选择只有一种批次特性的数据以及很多种不同批次特性(如颜色,尺码,尺寸等等)的数据,对比来看,另外也可以选择多条批次和单条批次来对比看,综合上述结果,选择适合与本系统的方式

本人的测试结果,如果是批次特性种类很少,比如就一种或两三种批次特性时,选择函数的方式可能会更快,但如果批次特性种类很多然后也要查很多批次的批次特性时,用取表的方式更快.

评论
添加红包

请填写红包祝福语或标题

红包个数最小为10个

红包金额最低5元

当前余额3.43前往充值 >
需支付:10.00
成就一亿技术人!
领取后你会自动成为博主和红包主的粉丝 规则
hope_wisdom
发出的红包
实付
使用余额支付
点击重新获取
扫码支付
钱包余额 0

抵扣说明:

1.余额是钱包充值的虚拟货币,按照1:1的比例进行支付金额的抵扣。
2.余额无法直接购买下载,可以购买VIP、付费专栏及课程。

余额充值