Supply Chain Management Blogs by Members
Learn about SAP SCM software from firsthand experiences of community members. Share your own post and join the conversation about supply chain management.
cancel
Showing results for 
Search instead for 
Did you mean: 
marianoc
Active Contributor

I would like to share an APO report to list Transportation Lanes.

The particularity of this report is that when the T-Lane uses an "All Products", the report will check those materials extended in the corresponding Locations and will show the list of products.

With the objective of avoid errors in the SNP run, an additional functionality is being tested and will be added to this report in order to allow the identification of Loops and ask for the user correction.

For example imagine that you have a transportation lane using All products between Locations ###1 and ###2:

In this case the report will be executed to see all the products included in this transportation lane. This will be the selection screen:

This will be the output:

This is the code:


*----------------------------------------------------------------------*
*   Program ZTRANSPORTATION_LANES                                                *
*----------------------------------------------------------------------*
********************************************************************
*                  PROGRAM DECLARATION
********************************************************************
* PROGRAM ID           ZTRANSPORTATION_LANES
* AUTHOR               Mariano Cabalen
* CREATE DATE          10/10/2013
* R/3 RELEASE VERSION  APO 7.0
* Based on
* DESCRIPTION          This report can be used to display Transportation
*                      Lanes in APO and translate the All Products considering
*                      where the Products are extended
***********************************************************************
* VERSION CONTROL (Most recent at bottom):
* DATE      AUTHOR     CTS REQ     DESCRIPTION
************************************************************************


REPORT ZTRANSPORTATION_LANES MESSAGE-ID zapo.


************************************************************************
* TABLES                                                               *
************************************************************************
TABLES: /SAPAPO/TRPROD, /SAPAPO/MATKEY, /SAPAPO/LOC, /SAPAPO/S_TRMSELMCOPY.

TYPE-POOLS: SLIS.

************************************************************************
* TYPES                                                                *
************************************************************************
TYPES:

BEGIN OF ty_list,
  TRNAME TYPE /SAPAPO/TRPROD-TRNAME,            " Model
  LOCFR TYPE /SAPAPO/TRPROD-LOCFR,              " Internal Number Source Location
  LOCTO TYPE /SAPAPO/TRPROD-LOCTO,              " Internal Number Target Location
  SPRKZ TYPE /SAPAPO/TRPROD-SPRKZ,              " Blocking Indicator for Source of Supply
  VALFR TYPE /SAPAPO/TRPROD-VALFR,              " Valid From
  VALTO TYPE /SAPAPO/TRPROD-VALTO,              " Valid To
  MATID TYPE /SAPAPO/TRPROD-MATID,              " Internal Number Product
  LOCNF TYPE /SAPAPO/LOC-LOCNO,                 " Source Locations
  LOCNT TYPE /SAPAPO/LOC-LOCNO,                 " Target Locations
  MATNR TYPE /SAPAPO/MATKEY-MATNR,              " Product
  DVALFR TYPE /SAPAPO/S_TRPRODALVIO-DVALFR,
  DVALTO TYPE /SAPAPO/S_TRPRODALVIO-DVALTO,
END OF ty_list,

BEGIN OF ty_locto,
  LOCTO TYPE /SAPAPO/TRPROD-LOCTO,              " Internal Number Target Location
  LOCNO TYPE /SAPAPO/LOC-LOCNO,                 " Target Location
END OF ty_locto,

BEGIN OF ty_locfr,
  LOCFR TYPE /SAPAPO/TRPROD-LOCFR,              " Internal Number Source Location
  LOCNO TYPE /SAPAPO/LOC-LOCNO,                 " Source Location
END OF ty_locfr,

BEGIN OF ty_matnr,
  MATID TYPE /SAPAPO/MATKEY-MATID,              " Internal Number Product
  MATNR TYPE /SAPAPO/MATKEY-MATNR,              " Product
END OF ty_matnr,

BEGIN OF ty_matloc,
  MATID TYPE /SAPAPO/MATLOC-MATID,              " Internal Number Product
  LOCID TYPE /SAPAPO/MATLOC-LOCID,              " Internal Number Location
  MATNR TYPE /SAPAPO/MATKEY-MATNR,
  LOCNO TYPE /SAPAPO/LOC-LOCNO,
END OF ty_matloc,

BEGIN OF ty_locaux,
  LOCNO TYPE /SAPAPO/LOC-LOCNO,
END OF ty_locaux.

************************************************************************
* CONSTANTS                                                            *
************************************************************************
CONSTANTS:
  c_x(1) VALUE 'X',
  c_e(1) VALUE 'E',
  c_eq(2) VALUE 'EQ',
  c_ne(2) VALUE 'NE',
  c_i(1) VALUE 'I',
  c_status_set TYPE slis_formname VALUE 'SET_PF_STATUS',
  c_user_command TYPE slis_formname VALUE 'USER_COMMAND',
  c_a(1)  VALUE 'X'.

************************************************************************
* DATA                                                                 *
************************************************************************
DATA:
  w_fieldcat TYPE slis_t_fieldcat_alv,          " Field Catalog Table
  w_layout TYPE slis_layout_alv,                " Layout Structure
  w_repid LIKE sy-cprog,                        " Report ID
  ZVALFR TYPE /SAPAPO/TRPROD-VALFR,              " Valid From
  ZVALTO TYPE /SAPAPO/TRPROD-VALTO,              " Valid To
  ZLOCNF TYPE /SAPAPO/LOC-LOCNO,
  ZLOCNT TYPE /SAPAPO/LOC-LOCNO,
  d1 TYPE d VALUE '00010101',
  d2 TYPE d VALUE '99991231',
  t1 TYPE t VALUE '000000',
  t2 TYPE t VALUE '235959'.


DATA:
*  Internal table for Records
   it_list TYPE STANDARD TABLE OF ty_list,
   wa_list TYPE ty_list,
*  Internal table for Records
   it_list1 TYPE STANDARD TABLE OF ty_list,
   wa_list1 TYPE ty_list,
*  Internal table for Records
   it_list2 TYPE STANDARD TABLE OF ty_list,
   wa_list2 TYPE ty_list,
*  Internal table for Records
   it_list3 TYPE STANDARD TABLE OF ty_list,
   wa_list3 TYPE ty_list,
*  Internal table for Records
   it_list3_count TYPE STANDARD TABLE OF ty_list,
   wa_list3_count TYPE ty_list,
*  Internal table for Records
   it_locto TYPE STANDARD TABLE OF ty_locto,
   wa_locto TYPE ty_locto,
*  Internal table for Records
   it_locfr TYPE STANDARD TABLE OF ty_locfr,
   wa_locfr TYPE ty_locfr,
*  Internal table for Records
   it_matnr TYPE STANDARD TABLE OF ty_matnr,
   wa_matnr TYPE ty_matnr,
*  Internal table for Records
   it_matloc_fr TYPE STANDARD TABLE OF ty_matloc,
   wa_matloc_fr TYPE ty_matloc,
*  Internal table for Records
   it_matloc_to TYPE STANDARD TABLE OF ty_matloc,
   wa_matloc_to TYPE ty_matloc,
*  Internal table for Records
   it_locaux TYPE STANDARD TABLE OF ty_locaux,
   wa_locaux TYPE ty_locaux.


*DATA: t_konv like konv occurs 0 with header line.

************************************************************************
* SELECT-OPTIONS                                                       *
************************************************************************

SELECTION-SCREEN begin of block BL1 with frame title text-BL1.
  SELECT-OPTIONS S_TRNAME for /SAPAPO/TRPROD-TRNAME.                      " Model
  SELECT-OPTIONS S_LOCNF for /SAPAPO/LOC-LOCNO.                           " Source Location
  SELECT-OPTIONS S_LOCNT for /SAPAPO/LOC-LOCNO.                           " Target Location
  SELECT-OPTIONS S_MATNR for /SAPAPO/MATKEY-MATNR.                        " Material
  SELECT-OPTIONS S_SPRKZ for /SAPAPO/TRPROD-SPRKZ.                        " Blocking Indicator for Source of Supply
  PARAMETERS P_VALFR LIKE /SAPAPO/AM_PSET-DATE_FROM DEFAULT SY-DATUM.     " Valid From
  PARAMETERS P_VALTO LIKE /SAPAPO/AM_PSET-DATE_TO DEFAULT '99991231'.     " Valid To
SELECTION-SCREEN end of block BL1.

SELECTION-SCREEN BEGIN OF BLOCK BL3 WITH FRAME TITLE TEXT-BL3.
PARAMETERS: p_send AS CHECKBOX DEFAULT 'X'.
SELECTION-SCREEN BEGIN OF LINE.
PARAMETERS: p_email0 LIKE adr6-smtp_addr.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN END OF BLOCK BL3.

************************************************************************
*                 I-N-I-T-I-A-L-I-Z-A-T-I-O-N                          *
************************************************************************
INITIALIZATION.


************************************************************************
* AT SELECTION-SCREEN                                                     *
************************************************************************
* Matchcode for Conditions.
*AT SELECTION-SCREEN ON VALUE-REQUEST FOR p_kschl.


************************************************************************
*  START OF DATA CONTROLS
************************************************************************
AT SELECTION-SCREEN.
  IF NOT p_send IS INITIAL and p_email0 IS INITIAL.
    MESSAGE e000 WITH text-e01.
  ENDIF.


************************************************************************
* START-OF-SELECTION                                                   *
************************************************************************
START-OF-SELECTION.

  PERFORM get_transportation_lanes.

  IF NOT it_list2[] IS INITIAL.
*   Show the ALV
    PERFORM listar_alv.
    IF NOT p_send IS INITIAL.
      PERFORM sending_file.
    ENDIF.
  ELSE.
*   No data for report
    MESSAGE I000 WITH text-E01.
  ENDIF.

*---------------------------------------------------------------------*
*       FORM get_transportation_lanes                                 *
*---------------------------------------------------------------------*
*       Get all the transportation lanes                              *
*---------------------------------------------------------------------*
FORM get_transportation_lanes.

  SELECT LOCID             " Target Locations
         LOCNO             " Target Locations
      INTO TABLE it_locto
      FROM /SAPAPO/LOC
      WHERE LOCNO IN S_LOCNT.

  SELECT LOCID             " Target Locations
         LOCNO             " Target Locations
      INTO TABLE it_locfr
      FROM /SAPAPO/LOC
      WHERE LOCNO IN S_LOCNF.

  SELECT MATID             " Target Locations
         MATNR             " Target Locations
      INTO TABLE it_matnr
      FROM /SAPAPO/MATKEY
      WHERE MATNR IN S_MATNR.

  SELECT a~MATID              " Internal Number Product
         a~LOCID              " Internal Number Locations
         b~MATNR              " Product
         c~LOCNO              " Location
      INTO CORRESPONDING FIELDS OF TABLE it_matloc_fr
      FROM /SAPAPO/MATLOC AS a
        INNER JOIN /SAPAPO/MATKEY AS b ON a~MATID = b~MATID
        INNER JOIN /SAPAPO/LOC AS c ON a~LOCID = c~LOCID
      FOR ALL ENTRIES IN it_locfr
      WHERE a~LOCID = it_locfr-locfr AND b~MATNR IN S_MATNR.

  SELECT a~MATID              " Internal Number Product
         a~LOCID              " Internal Number Locations
      INTO CORRESPONDING FIELDS OF TABLE it_matloc_to
      FROM /SAPAPO/MATLOC AS a
        INNER JOIN /SAPAPO/MATKEY AS b ON a~MATID = b~MATID
      FOR ALL ENTRIES IN it_locto
      WHERE a~LOCID = it_locto-locto AND b~MATNR IN S_MATNR.

  IF NOT P_VALFR IS INITIAL.
    CONVERT DATE P_VALFR TIME t1 DAYLIGHT SAVING TIME ' '  INTO TIME STAMP ZVALFR TIME ZONE 'UTC   '.
  ELSE.
    CONVERT DATE d1 TIME t1 DAYLIGHT SAVING TIME ' '  INTO TIME STAMP ZVALFR TIME ZONE 'UTC   '.
  ENDIF.

  IF NOT P_VALTO IS INITIAL.
    CONVERT DATE P_VALTO TIME t2 DAYLIGHT SAVING TIME ' '  INTO TIME STAMP ZVALTO TIME ZONE 'UTC   '.
  ELSE.
    CONVERT DATE d2 TIME t2 DAYLIGHT SAVING TIME ' '  INTO TIME STAMP ZVALTO TIME ZONE 'UTC   '.
  ENDIF.

  SELECT a~TRNAME             " Model
         a~LOCFR              " Internal Number Source Location
         a~LOCTO              " Internal Number Source Location
         a~SPRKZ              " Blocking Indicator for Source of Supply
         a~VALFR              " Valid From
         a~VALTO              " Valid To
         a~MATID              " Internal Number Product
         b~LOCNO              " Source Locations
      INTO CORRESPONDING FIELDS OF TABLE it_list
      FROM /SAPAPO/TRPROD AS a
        INNER JOIN /SAPAPO/LOC AS b ON a~LOCFR = b~LOCID
      FOR ALL ENTRIES IN it_locto
      WHERE b~LOCNO IN S_LOCNF AND a~LOCTO = it_locto-locto
        AND a~TRNAME IN S_TRNAME AND a~SPRKZ IN S_SPRKZ
        AND a~VALFR <= ZVALFR AND a~VALTO >= ZVALFR
        AND a~VALFR <= ZVALTO AND a~VALTO <= ZVALTO.

  IF sy-subrc = 0.
    LOOP AT it_list INTO wa_list.
      MOVE-CORRESPONDING wa_list TO wa_list1.
      READ TABLE it_locto INTO wa_locto WITH KEY locto = wa_list-locto.
      IF sy-subrc EQ 0.
        wa_list1-locnt = wa_locto-locno.
      ENDIF.
      READ TABLE it_locfr INTO wa_locfr WITH KEY locfr = wa_list-locfr.
      IF sy-subrc EQ 0.
        wa_list1-locnf = wa_locfr-locno.
      ENDIF.
      READ TABLE it_matnr INTO wa_matnr WITH KEY matid = wa_list-matid.
      IF sy-subrc EQ 0.
        wa_list1-matnr = wa_matnr-matnr.
      ELSEIF wa_list-matid IS INITIAL.
        wa_list1-matnr = 'All Products'.
      ELSE.
        CLEAR: wa_list1-matnr.
      ENDIF.
      DATA: t TYPE T VALUE '235500'.
      CONVERT TIME STAMP wa_list-valfr TIME ZONE 'UTC   ' INTO DATE wa_list1-dvalfr TIME t.
      CONVERT TIME STAMP wa_list-valto TIME ZONE 'UTC   ' INTO DATE wa_list1-dvalto TIME t.
      APPEND wa_list1 TO it_list1.
    ENDLOOP.
    CLEAR: wa_locto, wa_locfr.

    SORT it_list1 by MATNR LOCNF LOCNT.
    DELETE it_list1 WHERE matnr IS INITIAL.

  ENDIF.

  IF NOT it_list1[] IS INITIAL.
    LOOP AT it_list1 INTO wa_list1.
      MOVE-CORRESPONDING wa_list1 TO wa_list2.
      IF NOT wa_list1-matnr EQ 'All Products'.
        APPEND wa_list2 TO it_list2.
      ELSE.
        LOOP AT it_matloc_fr INTO wa_matloc_fr WHERE locid = wa_list1-locfr.
          READ TABLE it_matloc_to INTO wa_matloc_to WITH KEY matid = wa_matloc_fr-matid locid = wa_list1-locto.
          IF sy-subrc EQ 0.
            wa_list2-matnr = wa_matloc_fr-matnr.
            APPEND wa_list2 TO it_list2.
          ENDIF.
        ENDLOOP.
      ENDIF.
    ENDLOOP.
  ENDIF.

ENDFORM.                    " get_transportation_lanes

*---------------------------------------------------------------------*
*       FORM listar_alv                                               *
*---------------------------------------------------------------------*
*       Shows the report. Calls the REUSE_ALV_GRID_DISPLAY Function   *
*---------------------------------------------------------------------*
FORM listar_alv .

  w_repid = sy-repid.
  PERFORM init_layout CHANGING w_layout.
  PERFORM init_fieldcat CHANGING w_fieldcat.

* Call ALV GRID
  CALL FUNCTION 'REUSE_ALV_GRID_DISPLAY'
       EXPORTING
            i_callback_program       = w_repid
*            i_callback_user_command  = c_user_command
*            i_callback_pf_status_set = c_status_set
*            i_callback_pf_status_set = ' ' "c_status_set
            i_grid_title             = text-001
            is_layout                = w_layout
            it_fieldcat              = w_fieldcat
       TABLES
            t_outtab                 = IT_LIST2
       EXCEPTIONS
            program_error            = 1
            OTHERS                   = 2.

  IF sy-subrc <> 0.
    MESSAGE i010.
  ENDIF.

ENDFORM.                    " listar_alv


*---------------------------------------------------------------------*
*       FORM init_layout                                              *
*---------------------------------------------------------------------*
*       Inits Layout for ALV                                          *
*---------------------------------------------------------------------*
FORM init_layout  CHANGING p_w_layout TYPE slis_layout_alv.

  p_w_layout-zebra = c_x.
  p_w_layout-colwidth_optimize = c_x.
*  p_w_layout-box_fieldname = 'MARK'.

ENDFORM.                    " init_layout


*---------------------------------------------------------------------*
*       FORM init_fieldcat                                            *
*---------------------------------------------------------------------*
*       Inits Fieldcat for ALV                                        *
*---------------------------------------------------------------------*
FORM init_fieldcat  CHANGING p_w_fieldcat TYPE slis_t_fieldcat_alv.

  DATA: l_pos TYPE i VALUE 0,
        ls_fieldcat TYPE slis_fieldcat_alv.

* Model
  CLEAR ls_fieldcat.
  ADD 1 TO l_pos.
  ls_fieldcat-col_pos       = l_pos.
  ls_fieldcat-fieldname     = 'TRNAME'.
  ls_fieldcat-tabname       = 'IT_LIST2'.
  ls_fieldcat-ref_fieldname = 'TRNAME'.
  ls_fieldcat-ref_tabname = '/SAPAPO/TRPROD'.
  APPEND ls_fieldcat TO p_w_fieldcat.

* Source Location
  CLEAR ls_fieldcat.
  ADD 1 TO l_pos.
  ls_fieldcat-col_pos       = l_pos.
  ls_fieldcat-fieldname     = 'LOCNF'.
  ls_fieldcat-tabname       = 'IT_LIST2'.
  ls_fieldcat-ref_fieldname = 'LOCFR'.
  ls_fieldcat-ref_tabname = '/SAPAPO/TRPROD'.
  APPEND ls_fieldcat TO p_w_fieldcat.

* Target Location
  CLEAR ls_fieldcat.
  ADD 1 TO l_pos.
  ls_fieldcat-col_pos       = l_pos.
  ls_fieldcat-fieldname     = 'LOCNT'.
  ls_fieldcat-tabname       = 'IT_LIST2'.
  ls_fieldcat-ref_fieldname = 'LOCTO'.
  ls_fieldcat-ref_tabname = '/SAPAPO/TRPROD'.
  APPEND ls_fieldcat TO p_w_fieldcat.

* Product
  CLEAR ls_fieldcat.
  ADD 1 TO l_pos.
  ls_fieldcat-col_pos       = l_pos.
  ls_fieldcat-fieldname     = 'MATNR'.
  ls_fieldcat-tabname       = 'IT_LIST2'.
  ls_fieldcat-ref_fieldname = 'MATNR'.
  ls_fieldcat-ref_tabname = '/SAPAPO/MATKEY'.
  APPEND ls_fieldcat TO p_w_fieldcat.


* Blocking Indicator for Source of Supply
  CLEAR ls_fieldcat.
  ADD 1 TO l_pos.
  ls_fieldcat-col_pos       = l_pos.
  ls_fieldcat-fieldname     = 'SPRKZ'.
  ls_fieldcat-tabname       = 'IT_LIST2'.
  ls_fieldcat-ref_fieldname = 'SPRKZ'.
  ls_fieldcat-ref_tabname = '/SAPAPO/TRPROD'.
  APPEND ls_fieldcat TO p_w_fieldcat.


* Valid From
  CLEAR ls_fieldcat.
  ADD 1 TO l_pos.
  ls_fieldcat-col_pos       = l_pos.
  ls_fieldcat-fieldname     = 'DVALFR'.
  ls_fieldcat-tabname       = 'IT_LIST2'.
  ls_fieldcat-ref_fieldname = 'DVALFR'.
  ls_fieldcat-ref_tabname = '/SAPAPO/S_TRPRODALVIO'.
  APPEND ls_fieldcat TO p_w_fieldcat.

* Valid to
  CLEAR ls_fieldcat.
  ADD 1 TO l_pos.
  ls_fieldcat-col_pos       = l_pos.
  ls_fieldcat-fieldname     = 'DVALTO'.
  ls_fieldcat-tabname       = 'IT_LIST2'.
  ls_fieldcat-ref_fieldname = 'DVALTO'.
  ls_fieldcat-ref_tabname = '/SAPAPO/S_TRPRODALVIO'.
  APPEND ls_fieldcat TO p_w_fieldcat.

ENDFORM.                    " init_fieldcat


*&---------------------------------------------------------------------*
*&      Form  sending_file
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
*  -->  p1        text
*  <--  p2        text
*----------------------------------------------------------------------*
FORM sending_file.

*Emiail subject
  DATA : psubject(60) TYPE c .

*Data declaration for mail FM
  DATA:   it_packing_list LIKE sopcklsti1 OCCURS 0 WITH HEADER LINE,
          it_objbin LIKE solisti1 OCCURS 0 WITH HEADER LINE,
          it_receivers LIKE somlreci1 OCCURS 0 WITH HEADER LINE,
          it_objhead LIKE solisti1 OCCURS 0 WITH HEADER LINE,
          gd_sent_all(1) TYPE c,
          gd_doc_data LIKE sodocchgi1,
          v_tab_lines LIKE sy-tabix.

*Internal table for message body
  DATA:   it_message TYPE STANDARD TABLE OF solisti1 INITIAL SIZE 0
                  WITH HEADER LINE,
          it_messagewa LIKE LINE OF it_message        .

  DATA: cdatlo LIKE SY-DATLO,
        ctimlo LIKE SY-TIMLO.

  CONSTANTS : c_cret(2) TYPE c VALUE cl_abap_char_utilities=>cr_lf,
              c_tab(2) TYPE c VALUE cl_abap_char_utilities=>horizontal_tab.


  cdatlo = SY-DATLO.
  ctimlo = SY-TIMLO.

***************************************************************
* Subject
***************************************************************
CONCATENATE 'List of Transportation Lanes fr: ' CDATLO ' at: ' CTIMLO INTO psubject.

***************************************************************
* Mail Text
***************************************************************
  CLEAR it_message.
  REFRESH it_message.
  APPEND 'Dear,' TO it_message.
  APPEND 'This email is a notification of the List of Transportation Lanes.' TO it_message.
  CLEAR it_messagewa.
  it_messagewa = 'To view the list open the attached file'.
  APPEND it_messagewa TO it_message.
  APPEND 'Regards,' TO it_message.

***************************************************************
* Fill the document data.
***************************************************************
  gd_doc_data-doc_size = 1.
  gd_doc_data-obj_langu = sy-langu.
  gd_doc_data-obj_name  = 'SAPRPT'.
  gd_doc_data-obj_descr = psubject.
  gd_doc_data-sensitivty = 'F'.
  gd_doc_data-doc_size = ( v_tab_lines - 1 ) * 375 + STRLEN( it_message ).

***************************************************************
* Describe the body of the message
***************************************************************
  CLEAR it_packing_list.
  REFRESH it_packing_list.
  CLEAR it_packing_list-transf_bin.
  it_packing_list-head_start = 1.
  it_packing_list-head_num = 0.
  it_packing_list-body_start = 1.
  DESCRIBE TABLE it_message LINES it_packing_list-body_num.
  it_packing_list-doc_type = 'RAW'.
  APPEND it_packing_list.

***************************************************************
* Creation of the Excel document as attachment
***************************************************************
  CLEAR it_objbin.
  CONCATENATE 'Model'
              'Product'
              'Source Location'
              'Target Location'
              'Valid From'
              'Valid To'
              'Loop Indicator'
              into it_objbin SEPARATED BY c_tab.

  CONCATENATE c_cret it_objbin into it_objbin.
  APPEND it_objbin.
  LOOP AT it_list2 INTO wa_list2.
    CONCATENATE wa_list2-trname                " Model
                wa_list2-matnr                 " Product
                wa_list2-locnf                 " Source Location
                wa_list2-locnt                 " Target Location
                wa_list2-dvalfr                " Valid From
                wa_list2-dvalto                " Valid To
               into it_objbin SEPARATED BY c_tab.
    CONCATENATE c_cret it_objbin into it_objbin.
    APPEND it_objbin.
  ENDLOOP.
  DESCRIBE TABLE it_objbin LINES v_tab_lines.

  CONCATENATE 'Transportation_Lanes_List_' CDATLO '_' CTIMLO '.xls' INTO it_objhead.
  APPEND it_objhead.

***************************************************************
* Creation of the Excel document as attachment
***************************************************************
  it_packing_list-transf_bin = 'X'.
  it_packing_list-head_start = 1.
  it_packing_list-head_num = 1.
  it_packing_list-body_start = 1.
  it_packing_list-body_num = v_tab_lines..
  it_packing_list-doc_type = 'XLS'.
  it_packing_list-obj_name = 'Transportation_Lanes_List'(059).
  it_packing_list-obj_descr = 'Transportation_Lanes_List'(059).
  it_packing_list-doc_size = v_tab_lines * 375.
  APPEND it_packing_list.

***************************************************************
* Add the recipients email address
***************************************************************
  CLEAR it_receivers.
  it_receivers-receiver = p_email0.
  it_receivers-rec_type = 'U'.
  it_receivers-com_type = 'INT'.
  it_receivers-notif_del = 'X'.
  it_receivers-notif_ndel = 'X'.
  APPEND it_receivers.

***************************************************************
* Call the FM to post the message to SAPMAIL
***************************************************************

  CALL FUNCTION 'SO_NEW_DOCUMENT_ATT_SEND_API1'
      EXPORTING
          document_data                    = gd_doc_data
          put_in_outbox                    = 'X'
          commit_work                      = 'X'
      IMPORTING
          sent_to_all                      = gd_sent_all
*         NEW_OBJECT_ID                    =
      TABLES
          packing_list                     = it_packing_list
          OBJECT_HEADER                    = it_objhead
          CONTENTS_BIN                     = it_objbin
          CONTENTS_TXT                     = it_message
*         CONTENTS_HEX                     =
*         OBJECT_PARA                      =
*         OBJECT_PARB                      =
          receivers                        = it_receivers
      EXCEPTIONS
          too_many_receivers               = 1
          document_not_sent                = 2
          document_type_not_exist          = 3
          operation_no_authorization       = 4
          parameter_error                  = 5
          x_error                          = 6
          enqueue_error                    = 7
          OTHERS                           = 8.


  CASE sy-subrc.
    WHEN '0'.
      WAIT UP TO 2 SECONDS.
      SUBMIT rsconn01 WITH mode = 'INT' AND RETURN.
      IF SY-SUBRC EQ 0.
        MESSAGE S000 WITH text-S01.
      ELSE.
        MESSAGE E000 WITH text-E04.
      ENDIF.
  ENDCASE.

ENDFORM.                    " sending_file

Labels in this area