zoukankan      html  css  js  c++  java
  • ABAP如何快速从BSEG读取数据

    由于bseg表很大,而且表的索引字段是:

    BUKRS - Company Code
    BELNR - Accounting Document Number
    GJAHR - Fiscal Year
    BUZEI - Line Item Number

     访问此表最佳的是包含所有的索引字段,但在实际应用是很少能达到的。但要有好的性能根据经验必须要有公司和凭证号作为查询条件。为了达到这一点,我可以根据条件不同而使用不同sap的其他表,先查出公司和凭证号,再去读取BSEG表

    代码如下:

    注意:该程序包含了各种条件的查询,程序员可以根据自己应用需求选择对应一个的子程序来读取公司和凭证号。

    REPORT ztest_select.

    * Tables ***************************************************************
    TABLES: bkpf, bseg,
            covp, csks,
            glpca,
            bsis, bsas, bsid, bsad, bsik, bsak,
            ekbe, aufk,
            vbfa, vbak,
            vapma,
            fmifiit,
            payr.

    * Global Data **********************************************************

    TYPES: BEGIN OF doc,
            bukrs TYPE bseg-bukrs,
            belnr TYPE bseg-belnr,
            gjahr TYPE bseg-gjahr,
            buzei TYPE bseg-buzei,
          END   OF doc.

    DATA: doc_int  TYPE TABLE OF doc,
          doc_wa   TYPE          doc,
          w_repid  TYPE sy-repid VALUE sy-repid,
          no_lines TYPE sy-tabix.

    * Selection Screen *****************************************************
    PARAMETERS: p_gjahr TYPE covp-refgj OBLIGATORY.
    SELECTION-SCREEN SKIP.
    PARAMETERS: p_kokrs TYPE csks-kokrs OBLIGATORY,
                p_kostl TYPE csks-kostl,
                p_prctr TYPE glpca-rprctr,
                p_aufnr TYPE aufk-aufnr.
    SELECTION-SCREEN SKIP.
    PARAMETERS: p_bukrs TYPE bsis-bukrs OBLIGATORY,
                p_budat TYPE bkpf-budat,
                p_ebeln TYPE ekko-ebeln,
                p_hkont TYPE bsis-hkont,
                p_lifnr TYPE bsik-lifnr,
                p_kunnr TYPE bsid-kunnr.
    SELECTION-SCREEN SKIP.
    PARAMETERS: p_vbeln TYPE vbak-vbeln.
    SELECTION-SCREEN SKIP.
    PARAMETERS: p_matnr TYPE vapma-matnr.
    SELECTION-SCREEN SKIP.
    PARAMETERS: p_fikrs TYPE fmifiit-fikrs,
                p_fistl TYPE fmifiit-fistl,
                p_fonds TYPE fmifiit-fonds.
    SELECTION-SCREEN ULINE.
    PARAMETERS: p_hbkid TYPE payr-hbkid,
                p_hktid TYPE payr-hktid,
                p_rzawe TYPE payr-rzawe,
                p_chect TYPE payr-chect.

    START-OF-SELECTION.

    * Retrieve document numbers based on different requirements

    * Posting Date (用日期做查询条件)
      PERFORM posting_date_actuals
        USING p_bukrs
              p_budat.

    * Cost Center
      PERFORM cost_center_actuals
        USING p_kokrs
              p_kostl
              p_gjahr.

    * GL Account
      PERFORM gl_actuals
        USING p_bukrs
              p_hkont
              p_gjahr.

    * Vendor
      PERFORM vendor_actuals
        USING p_bukrs
              p_lifnr
              p_gjahr.

    * Customer
      PERFORM customer_actuals
        USING p_bukrs
              p_kunnr
              p_gjahr.

    * Purchase Order
      PERFORM po_actuals
        USING p_ebeln.

    * Sales Order
      PERFORM so_actuals
        USING p_vbeln.

    * Order
      PERFORM order_actuals
        USING p_aufnr
              p_gjahr.

    * Fund/Fund Center
      PERFORM fm_actuals
        USING p_fikrs
              p_gjahr
              p_fistl
              p_fonds.

    * Profit Center
      PERFORM profit_center_actuals
        USING p_kokrs
              p_prctr
              p_gjahr.

    * Material
      PERFORM material_actuals
        USING p_matnr
              p_gjahr.

    * Cheque number
      PERFORM cheque_actuals
        USING p_hbkid
              p_hktid
              p_chect.

    *&---------------------------------------------------------------------*
    *&      Form  posting_date_actuals
    *&---------------------------------------------------------------------*
    *       Use one of the secondary indices of BKPF to retrieve the
    *       document number
    *----------------------------------------------------------------------*
    FORM posting_date_actuals
      USING    bukrs
               budat.

      DATA: disp_date(10).

      CHECK NOT budat IS INITIAL.

    * Uses index BKPF~2 (4.7)
      SELECT bukrs belnr gjahr
        INTO TABLE doc_int
        UP TO 100 ROWS
        FROM bkpf
        WHERE bukrs = bukrs  AND
    * Normally, you would probably only want normal documents, that is
    * documents with BSTAT = ' '. So you would change the next line.
    * On the other hand, you might want documents for all values of BSTAT,
    * but not want to hardcode the values. In that case, you can retrieve
    * values from the domain of BSTAT and put them in a range table and
    * use the range table in the next line.
              bstat IN (' ', 'A', 'B', 'D', 'M', 'S', 'V', 'W', 'Z') AND
              budat = budat.

      CHECK sy-subrc = 0.
      WRITE budat TO disp_date.

      PERFORM display_documents
        TABLES doc_int
        USING 'Posting date'
              disp_date
              space
              space.

    ENDFORM.                    " posting_date_actuals

    *&---------------------------------------------------------------------*
    *&      Form  cost_center_actuals
    *&---------------------------------------------------------------------*
    *       Retrieve documents for a cost center
    *----------------------------------------------------------------------*
    FORM cost_center_actuals
      USING    kokrs
               kostl
               gjahr.

      DATA: covp_int TYPE TABLE OF covp,
            disp_cc(10).

      CHECK NOT kostl IS INITIAL.

    * Uses primary index (4.7)
      SELECT SINGLE objnr
        FROM csks
        INTO csks-objnr
        WHERE kokrs = kokrs
          AND kostl = kostl.

      CHECK sy-subrc = 0.

    * COVP is a view. This uses index COEP~1 (4.7)
      SELECT refbk refbn refgj refbz
        FROM covp
        INTO TABLE doc_int
        UP TO 100 ROWS
        WHERE lednr = '00'
          AND objnr = csks-objnr
          AND gjahr = gjahr
          AND wrttp IN ('04', '11')
          AND versn = '000'.

      CHECK sy-subrc = 0.

      CALL FUNCTION 'CONVERSION_EXIT_ALPHA_OUTPUT'
        EXPORTING
          input  = kostl
        IMPORTING
          output = disp_cc.

      PERFORM display_documents
        TABLES doc_int
        USING 'Cost Center'
              disp_cc
              space
              space.

    ENDFORM.                    " cost_center_actuals

    *&---------------------------------------------------------------------*
    *&      Form  gl_actuals
    *&---------------------------------------------------------------------*
    *       BKPF and BSEG have a number of secondary index tables. These are
    *       tables that are indexed by GL customer or vendor number and have
    *       data that is in both BKPF and BSEG. These secondary index tables
    *       that have an 'i' in the third character of the name contain open
    *       items. Those with an 'a' contain cleared items. In practice, you
    *       may only one or the other. In this program I am retrieving both.
    *
    *       Here we get documents related to a GL.
    *----------------------------------------------------------------------*
    FORM gl_actuals
      USING    bukrs
               hkont
               gjahr.

      DATA: disp_gl(10).

      CHECK NOT hkont IS INITIAL.

    * Uses primary index (4.7)
      SELECT bukrs belnr gjahr buzei
        FROM bsis
        INTO TABLE doc_int
        UP TO 100 ROWS
        WHERE bukrs = bukrs
          AND hkont = hkont
          AND gjahr = gjahr.

    * Uses primary index (4.7)
      SELECT bukrs belnr gjahr buzei
        FROM bsas
        APPENDING TABLE doc_int
        UP TO 100 ROWS
        WHERE bukrs = bukrs
          AND hkont = hkont
          AND gjahr = gjahr.

      DESCRIBE TABLE doc_int LINES no_lines.
      CHECK no_lines > 0.

      CALL FUNCTION 'CONVERSION_EXIT_ALPHA_OUTPUT'
        EXPORTING
          input  = hkont
        IMPORTING
          output = disp_gl.

      PERFORM display_documents
        TABLES doc_int
        USING 'GL Account'
              disp_gl
              space
              space.

    ENDFORM.                    " gl_actuals

    *&---------------------------------------------------------------------*
    *&      Form  vendor_actuals
    *&---------------------------------------------------------------------*
    *       Here we get documents related to a vendor.
    *----------------------------------------------------------------------*
    FORM vendor_actuals
      USING    bukrs
               lifnr
               gjahr.

      DATA: disp_vendor(10).

      CHECK NOT lifnr IS INITIAL.

    * Uses primary index (4.7)
      SELECT bukrs belnr gjahr buzei
        FROM bsik
        INTO TABLE doc_int
        UP TO 100 ROWS
        WHERE bukrs = bukrs
          AND lifnr = lifnr
          AND gjahr = gjahr.

    * Uses primary index (4.7)
      SELECT bukrs belnr gjahr buzei
        FROM bsak
        APPENDING TABLE doc_int
        UP TO 100 ROWS
        WHERE bukrs = bukrs
          AND lifnr = lifnr
          AND gjahr = gjahr.

      DESCRIBE TABLE doc_int LINES no_lines.
      CHECK no_lines > 0.

      CALL FUNCTION 'CONVERSION_EXIT_ALPHA_OUTPUT'
        EXPORTING
          input  = lifnr
        IMPORTING
          output = disp_vendor.

      PERFORM display_documents
        TABLES doc_int
        USING 'Vendor'
              disp_vendor
              space
              space.


    ENDFORM.                    " vendor_actuals

    *&---------------------------------------------------------------------*
    *&      Form  customer_actuals
    *&---------------------------------------------------------------------*
    *       Here we get documents related to a customer.
    *----------------------------------------------------------------------*
    FORM customer_actuals
      USING  bukrs
             kunnr
             gjahr.

      DATA: disp_customer(10).

      CHECK NOT kunnr IS INITIAL.

    * Uses primary index (4.7)
      SELECT bukrs belnr gjahr buzei
        FROM bsid
        INTO TABLE doc_int
        UP TO 100 ROWS
        WHERE bukrs = bukrs
          AND kunnr = kunnr
          AND gjahr = gjahr.

    * Uses primary index (4.7)
      SELECT bukrs belnr gjahr buzei
        FROM bsad
        APPENDING TABLE doc_int
        UP TO 100 ROWS
        WHERE bukrs = bukrs
          AND kunnr = kunnr
          AND gjahr = gjahr.

      DESCRIBE TABLE doc_int LINES no_lines.
      CHECK no_lines > 0.

      CALL FUNCTION 'CONVERSION_EXIT_ALPHA_OUTPUT'
        EXPORTING
          input  = kunnr
        IMPORTING
          output = disp_customer.

      PERFORM display_documents
        TABLES doc_int
        USING 'Customer'
              disp_customer
              space
              space.

    ENDFORM.                    " customer_actuals

    *&---------------------------------------------------------------------*
    *&      Form  po_actuals
    *&---------------------------------------------------------------------*
    *       Table BKPF has a useful index on AWTYP and AWKEY. Here, we use
    *       this to retrieve documents for purchase orders.
    *----------------------------------------------------------------------*
    FORM po_actuals
      USING    ebeln.

      TYPES: BEGIN OF ekbe_type,
               belnr TYPE ekbe-belnr,
               gjahr TYPE ekbe-gjahr,
               vgabe TYPE ekbe-vgabe,
             END   OF ekbe_type.

      DATA: ekbe_int TYPE TABLE OF ekbe_type,
            ekbe_wa  TYPE          ekbe_type.

      DATA: v_reference    TYPE bkpf-awtyp,           "Reference procedure
            v_objectkey    TYPE bkpf-awkey.           "Object key

      DATA:disp_po(10).

      CHECK NOT ebeln IS INITIAL.

    * Uses primary index (4.7)
      SELECT belnr gjahr
        FROM ekbe
        INTO TABLE ekbe_int
        UP TO 100 ROWS
        WHERE ebeln = ebeln
        AND vgabe IN ('1', '2').                      "1 - GR, 2 - IR

      CHECK sy-subrc = 0.

      SORT ekbe_int.
      DELETE ADJACENT DUPLICATES FROM ekbe_int.

      LOOP AT ekbe_int INTO ekbe_wa.
        v_objectkey+00(10) = ekbe_wa-belnr.
        v_objectkey+10(10) = ekbe_wa-gjahr.           "BELNR+YEAR

        IF ekbe_wa-vgabe = '1'.
          v_reference = 'MKPF'.
        ELSE.
          v_reference = 'RMRP'.
        ENDIF.

    * Uses index BKPF~4 (4.7)
        SELECT SINGLE bukrs belnr gjahr               "Accounting Doc Header
          FROM bkpf
          INTO doc_wa
          WHERE awtyp =  v_reference
            AND awkey =  v_objectkey.
        IF sy-subrc = 0.
          APPEND doc_wa TO doc_int.
        ENDIF.
      ENDLOOP.

      CHECK no_lines > 0.

      CALL FUNCTION 'CONVERSION_EXIT_ALPHA_OUTPUT'
        EXPORTING
          input  = ebeln
        IMPORTING
          output = disp_po.

      PERFORM display_documents
        TABLES doc_int
        USING 'Purchase Order'
              disp_po
              space
              space.

    ENDFORM.                    " po_actuals

    *&---------------------------------------------------------------------*
    *&      Form  so_actuals
    *&---------------------------------------------------------------------*
    *       Use AWTYP and AWKEY to retrieve documents related to sales
    *----------------------------------------------------------------------*
    FORM so_actuals  USING    vbeln.

      TYPES: BEGIN OF vbfa_type,
               vbeln TYPE vbfa-vbeln,
             END   OF vbfa_type.

      DATA: vbfa_int TYPE TABLE OF vbfa_type,
            vbfa_wa  TYPE          vbfa_type.

      DATA: v_reference    TYPE bkpf-awtyp,           "Reference procedure
            v_objectkey    TYPE bkpf-awkey.           "Object key

      DATA:disp_so(10).

      CHECK NOT vbeln IS INITIAL.

    * Uses primary index (4.7)
      SELECT vbeln
        FROM vbfa
        INTO TABLE vbfa_int
        UP TO 100 ROWS
        WHERE vbelv   = vbeln
          AND vbtyp_n = 'P'.                          "Debit memo

      CHECK sy-subrc = 0.

      SORT vbfa_int.
      DELETE ADJACENT DUPLICATES FROM vbfa_int.

      LOOP AT vbfa_int INTO vbfa_wa.
        v_objectkey+00(10) = vbfa_wa-vbeln.           "BELNR
        v_reference        = 'VBRK'.

    * Uses index BKPF~4 (4.7)
        SELECT SINGLE bukrs belnr gjahr               "Accounting Doc Header
          FROM bkpf
          INTO doc_wa
          WHERE awtyp =  v_reference
            AND awkey =  v_objectkey.
        IF sy-subrc = 0.
          APPEND doc_wa TO doc_int.
        ENDIF.
      ENDLOOP.

      DESCRIBE TABLE doc_int LINES no_lines.
      CHECK no_lines > 0.

      CALL FUNCTION 'CONVERSION_EXIT_ALPHA_OUTPUT'
        EXPORTING
          input  = vbeln
        IMPORTING
          output = disp_so.

      PERFORM display_documents
        TABLES doc_int
        USING 'Sales Document'
              disp_so
              space
              space.

    ENDFORM.                    " so_actuals

    *&---------------------------------------------------------------------*
    *&      Form  order_actuals
    *&---------------------------------------------------------------------*
    *       Retrieve documents related to an order
    *----------------------------------------------------------------------*
    FORM order_actuals
      USING    aufnr
               gjahr.

      DATA: disp_order(10).

      CHECK NOT aufnr IS INITIAL.

    * Uses primary index (4.7)
      SELECT SINGLE objnr
        FROM aufk
        INTO aufk-objnr
        WHERE aufnr = aufnr.

      CHECK sy-subrc = 0.

    * COVP is a view. This uses index COEP~1 (4.7)
      SELECT refbk refbn refgj refbz
        FROM covp
        INTO TABLE doc_int
        UP TO 100 ROWS
        WHERE lednr = '00'
          AND objnr = aufk-objnr
          AND gjahr = gjahr
          AND wrttp IN ('04', '11')
          AND versn = '000'.

      CHECK sy-subrc = 0.

      CALL FUNCTION 'CONVERSION_EXIT_ALPHA_OUTPUT'
        EXPORTING
          input  = aufnr
        IMPORTING
          output = disp_order.

      PERFORM display_documents
        TABLES doc_int
        USING 'Order'
              disp_order
              space
              space.

    ENDFORM.                    " order_actuals

    *&---------------------------------------------------------------------*
    *&      Form  FM_actuals
    *&---------------------------------------------------------------------*
    *       Not many institutions use Funds Management, but if you do, this
    *       is how to relate funds management documents to FI documents.
    *----------------------------------------------------------------------*
    FORM fm_actuals
      USING    fikrs
               gjahr
               fistl
               fonds.

      DATA: disp_cfc(10),
            disp_fund(10).

      CHECK NOT fikrs IS INITIAL AND
            NOT fistl IS INITIAL.

    * Uses index FMIFIIT~3 (4.7)
      SELECT bukrs knbelnr kngjahr knbuzei
        FROM  fmifiit
        INTO TABLE doc_int
        UP TO 100 ROWS
             WHERE  fistl  = fistl
             AND    fonds  = fonds.

      CHECK sy-subrc = 0.

      CALL FUNCTION 'CONVERSION_EXIT_ALPHA_OUTPUT'
        EXPORTING
          input  = fistl
        IMPORTING
          output = disp_cfc.

      IF NOT fonds IS INITIAL.
        CALL FUNCTION 'CONVERSION_EXIT_ALPHA_OUTPUT'
          EXPORTING
            input  = fonds
          IMPORTING
            output = disp_fund.
      ENDIF.

      PERFORM display_documents
        TABLES doc_int
        USING 'Fund Center'
              disp_cfc
              'Fund'
              disp_fund.

    ENDFORM.                    " FM_actuals

    *&---------------------------------------------------------------------*
    *&      Form  profit_center_actuals
    *&---------------------------------------------------------------------*
    *       Retrieve documents related to a profit center
    *----------------------------------------------------------------------*
    FORM profit_center_actuals
      USING    kokrs
               prctr
               gjahr.

      DATA: disp_pc(10).

      CHECK NOT prctr IS INITIAL.

    * This uses index GLPCA~1 (4.7)
      SELECT rbukrs refdocnr refryear refdocln
        FROM glpca
        INTO TABLE doc_int
        UP TO 100 ROWS
        WHERE kokrs  = kokrs
          AND ryear  = gjahr
          AND rprctr = prctr
          AND awtyp  = 'BKPF'.

      CHECK sy-subrc = 0.

      CALL FUNCTION 'CONVERSION_EXIT_ALPHA_OUTPUT'
        EXPORTING
          input  = prctr
        IMPORTING
          output = disp_pc.

      PERFORM display_documents
        TABLES doc_int
        USING 'Profit Center'
              disp_pc
              space
              space.

    ENDFORM.                    " profit_center_actuals

    *&---------------------------------------------------------------------*
    *&      Form  material_actuals
    *&---------------------------------------------------------------------*
    *       Get FI documents for a material.
    *       For purchase orders get:
    *         goods receipts
    *         invoice receipts
    *       For sales orders get:
    *         debit memos
    *----------------------------------------------------------------------*
    FORM material_actuals
      USING    matnr
               gjahr.

      TYPES: BEGIN OF ekpo_type,
               ebeln TYPE ekpo-ebeln,
               ebelp TYPE ekpo-ebelp,
             END   OF ekpo_type.

      TYPES: BEGIN OF ekbe_type,
               belnr TYPE ekbe-belnr,
               gjahr TYPE ekbe-gjahr,
               vgabe TYPE ekbe-vgabe,
             END   OF ekbe_type.

      TYPES: BEGIN OF vapma_type,
               vbeln TYPE vapma-vbeln,
               posnr TYPE vapma-posnr,
             END   OF vapma_type.

      TYPES: BEGIN OF vbfa_type,
               vbeln TYPE vbfa-vbeln,
               posnv TYPE vbfa-posnv,
             END   OF vbfa_type.

      DATA: ekpo_int TYPE TABLE OF ekpo_type,
            ekpo_wa  TYPE          ekpo_type.

      DATA: ekbe_int TYPE TABLE OF ekbe_type,
            ekbe_wa  TYPE          ekbe_type.

      DATA: vapma_int TYPE TABLE OF vapma_type,
            vapma_wa  TYPE          vapma_type.

      DATA: v_reference    TYPE bkpf-awtyp,           "Reference procedure
            v_objectkey    TYPE bkpf-awkey.           "Object key

      DATA: vbfa_int TYPE TABLE OF vbfa_type,
            vbfa_wa  TYPE          vbfa_type.

      DATA: disp_mat(10).

      CHECK NOT matnr IS INITIAL.

    * First, find purchase orders for the material
    * This uses index EKPO~1 (4.7)
      SELECT ebeln ebelp
        FROM ekpo
        INTO TABLE ekpo_int
        UP TO 100 ROWS
        WHERE matnr = matnr.

    * Now get the FI document numbers as above
    * Uses primary index (4.7)
      SELECT belnr gjahr vgabe
        FROM ekbe
        INTO TABLE ekbe_int
        UP TO 100 ROWS
        FOR ALL ENTRIES IN ekpo_int
        WHERE ebeln = ekpo_int-ebeln
          AND ebelp = ekpo_int-ebelp
          AND vgabe IN ('1', '2').                      "1 - GR, 2 - IR

      CHECK sy-subrc = 0.

      SORT ekbe_int.
      DELETE ADJACENT DUPLICATES FROM ekbe_int.

      LOOP AT ekbe_int INTO ekbe_wa.
        v_objectkey+00(10) = ekbe_wa-belnr.
        v_objectkey+10(10) = ekbe_wa-gjahr.           "BELNR+YEAR

        IF ekbe_wa-vgabe = '1'.
          v_reference = 'MKPF'.
        ELSE.
          v_reference = 'RMRP'.
        ENDIF.

    * Uses index BKPF~4 (4.7)
        SELECT SINGLE bukrs belnr gjahr               "Accounting Doc Header
          FROM bkpf
          INTO doc_wa
          WHERE awtyp =  v_reference
            AND awkey =  v_objectkey.
        IF sy-subrc = 0.
          APPEND doc_wa TO doc_int.
        ENDIF.
      ENDLOOP.

    * Next get the sales orders for the material

    * Note - I am using an artificial date range here because of archiving
    * in our system. Feel free to remove it.
      SELECT vbeln posnr
        FROM vapma
        INTO TABLE vapma_int
        UP TO 100 ROWS
        WHERE matnr = matnr
          AND audat BETWEEN '20070101' AND '20071231'.

    * Uses primary index (4.7)
      SELECT vbeln posnv
        FROM vbfa
        INTO TABLE vbfa_int
        FOR ALL ENTRIES IN vapma_int
        WHERE vbelv   = vapma_int-vbeln
          AND posnv   = vapma_int-posnr
          AND vbtyp_n = 'P'.                          "Debit memo

      CHECK sy-subrc = 0.

      SORT vbfa_int.
      DELETE ADJACENT DUPLICATES FROM vbfa_int.

      LOOP AT vbfa_int INTO vbfa_wa.
        CLEAR: v_objectkey,
               v_reference.
        v_objectkey+00(10) = vbfa_wa-vbeln.           "BELNR
        v_reference        = 'VBRK'.

    * Uses index BKPF~4 (4.7)
        SELECT SINGLE bukrs belnr gjahr               "Accounting Doc Header
          FROM bkpf
          INTO doc_wa
          WHERE awtyp =  v_reference
            AND awkey =  v_objectkey.
        IF sy-subrc = 0.
          APPEND doc_wa TO doc_int.
        ENDIF.
      ENDLOOP.

      DESCRIBE TABLE doc_int LINES no_lines.
      CHECK no_lines > 0.

      CALL FUNCTION 'CONVERSION_EXIT_ALPHA_OUTPUT'
        EXPORTING
          input  = matnr
        IMPORTING
          output = disp_mat.

      PERFORM display_documents
        TABLES doc_int
        USING 'Material'
              disp_mat
              space
              space.

    ENDFORM.                    " material_actuals

    *&---------------------------------------------------------------------*
    *&      Form  cheque_actuals
    *&---------------------------------------------------------------------*
    *       Retrieve FI documents for a cheque. We are assuming Accounts
    *       Payable related.
    *----------------------------------------------------------------------*
    FORM cheque_actuals
      USING    hbkid
               hktid
               chect.
      DATA: belnr TYPE payr-vblnr,
            gjahr TYPE payr-gjahr,
            lifnr TYPE payr-lifnr,
            laufd TYPE payr-laufd,
            disp_cheque(13).

      CHECK NOT p_chect IS INITIAL.

    * Retrieve the cheque data using the primary key (4.7)
    * We are assuming a vendor payment here
      SELECT SINGLE vblnr gjahr lifnr laufd
        FROM  payr
        INTO (belnr, gjahr, lifnr, laufd )
        WHERE  zbukr  = p_bukrs
          AND  hbkid  = p_hbkid
          AND  hktid  = p_hktid
          AND  rzawe  = p_rzawe
          AND  chect  = p_chect.

    * Now get the accounting documents
      SELECT bukrs belnr gjahr
        FROM  bsak
        INTO TABLE doc_int
             WHERE  bukrs  = p_bukrs
             AND    lifnr  = lifnr
             AND    umsks  = ' '
             AND    umskz  = ' '
             AND    augdt  = laufd
             AND    augbl  = belnr
             AND    gjahr  = gjahr.

      DESCRIBE TABLE doc_int LINES no_lines.
      CHECK no_lines > 0.

      CALL FUNCTION 'CONVERSION_EXIT_ALPHA_OUTPUT'
        EXPORTING
          input  = chect
        IMPORTING
          output = disp_cheque.

      PERFORM display_documents
        TABLES doc_int
        USING 'Cheque number'
              disp_cheque
              space
              space.

    ENDFORM.                    " cheque_actuals

    *&---------------------------------------------------------------------*
    *&      Form  display_documents
    *&---------------------------------------------------------------------*
    *       At this point, you have the company code, document number and
    *       fiscal year in table DOC_INT. Here, I just use a standard SAP
    *       function module and transaction to display documents and
    *       details, but you could use the same information to retrieve
    *       document data from BKPF and/or BSEG.
    *----------------------------------------------------------------------*
    FORM display_documents
      TABLES   doc_int STRUCTURE doc_wa
      USING    doc_source_1
               source_value_1
               doc_source_2
               source_value_2.

      TYPE-POOLS: slis.

      DATA: sel     TYPE  slis_selfield.
      DATA: title   TYPE string.

      CONCATENATE 'FI line items for' doc_source_1 source_value_1
                   INTO title SEPARATED BY space.

      IF NOT source_value_2 IS INITIAL.
        CONCATENATE title doc_source_2 source_value_2
                    INTO title SEPARATED BY space.
      ENDIF.

      CALL FUNCTION 'REUSE_ALV_POPUP_TO_SELECT'
        EXPORTING
          i_title                 = title
          i_selection             = 'X'
          i_tabname               = 'BSEG'
          i_structure_name        = 'BSEG'
          i_callback_user_command = 'USER_COMMAND'
          i_callback_program      = w_repid
        IMPORTING
          es_selfield             = sel
        TABLES
          t_outtab                = doc_int.

      IF NOT sel IS INITIAL.
        READ TABLE doc_int INDEX sel-tabindex.
        SET PARAMETER ID 'BUK' FIELD doc_int-bukrs.
        SET PARAMETER ID 'BLN' FIELD doc_int-belnr.
        SET PARAMETER ID 'GJR' FIELD doc_int-gjahr.
        CALL TRANSACTION 'FB03' AND SKIP FIRST SCREEN.
      ENDIF.

    ENDFORM.                    " display_documents

  • 相关阅读:
    494. Target Sum 添加标点符号求和
    636. Exclusive Time of Functions 进程的执行时间
    714. Best Time to Buy and Sell Stock with Transaction Fee有交易费的买卖股票
    377. Combination Sum IV 返回符合目标和的组数
    325. Maximum Size Subarray Sum Equals k 和等于k的最长子数组
    275. H-Index II 递增排序后的论文引用量
    274. H-Index论文引用量
    RabbitMQ学习之HelloWorld(1)
    java之struts2的数据处理
    java之struts2的action的创建方式
  • 原文地址:https://www.cnblogs.com/xiaomaohai/p/6157085.html
Copyright © 2011-2022 走看看