Homelab, Linux, JS & ABAP (~˘▾˘)~
 

[ABAP] Import Transport from ZIP

Report to import a ZIP file, containing the cofiles and data parts of a transport request. Related reports:
https://nocin.eu/abap-download-transport-as-zip/
https://nocin.eu/abap-create-toc-for-a-given-transport-release-it-and-download-it-as-zip/

This report can be handy, especially since S/4HANA 2023 seems to have restricted the “classic” import way by using TCode CG3Y and CG3Z. See note 1949906, where it is recommended to create a custom report.

*&---------------------------------------------------------------------*
*& Report Z_IMPORT_TRANSPORT_FROM_ZIP
*&---------------------------------------------------------------------*
*&
*&---------------------------------------------------------------------*
REPORT z_import_transport_from_zip.

SELECTION-SCREEN BEGIN OF BLOCK bl02 WITH FRAME TITLE TEXT-t02.
  PARAMETERS p_lcldir TYPE string  LOWER CASE OBLIGATORY DEFAULT 'C:\temp\'.
  PARAMETERS p_sapdir TYPE char255 LOWER CASE OBLIGATORY.
SELECTION-SCREEN END OF BLOCK bl02.

SELECTION-SCREEN BEGIN OF BLOCK bl03 WITH FRAME.
  PARAMETERS p_import TYPE boolean DEFAULT 'X' AS CHECKBOX.
SELECTION-SCREEN END OF BLOCK bl03.


AT SELECTION-SCREEN OUTPUT.

  CALL 'C_SAPGPARAM' ID 'NAME' FIELD 'DIR_TRANS' ID 'VALUE' FIELD p_sapdir.


AT SELECTION-SCREEN ON VALUE-REQUEST FOR p_lcldir.

  DATA lt_files  TYPE filetable.
  DATA lv_rc     TYPE i.
  DATA lv_action TYPE i.

  TRY.
      cl_gui_frontend_services=>file_open_dialog( EXPORTING window_title      = 'Import'
                                                            default_extension = '.zip'
                                                            initial_directory = 'C:\temp\'
                                                            multiselection    = abap_false
                                                  CHANGING  file_table        = lt_files
                                                            rc                = lv_rc
                                                            user_action       = lv_action ).
      IF lv_action = cl_gui_frontend_services=>action_ok AND lines( lt_files ) > 0.
        p_lcldir = lt_files[ 1 ]-filename.
      ENDIF.
    CATCH cx_root INTO DATA(e_text).
      MESSAGE e_text->get_text( ) TYPE 'I'.
  ENDTRY.


START-OF-SELECTION.

  DATA lv_zip_size TYPE i.
  DATA lt_zip_data TYPE solix_tab.
  DATA lv_xstring  TYPE xstring.

  cl_gui_frontend_services=>gui_upload( EXPORTING filename   = p_lcldir
                                                  filetype   = 'BIN'
                                        IMPORTING filelength = lv_zip_size
                                        CHANGING  data_tab   = lt_zip_data ).

  CALL FUNCTION 'SCMS_BINARY_TO_XSTRING'
    EXPORTING
      input_length = lv_zip_size
    IMPORTING
      buffer       = lv_xstring
    TABLES
      binary_tab   = lt_zip_data.


  " write zip content to filesystem
  DATA(lo_zipper)      = NEW cl_abap_zip( ).
  DATA(lt_zip_entries) = lo_zipper->splice( lv_xstring ).
  lo_zipper->load( lv_xstring ).

  LOOP AT lt_zip_entries INTO DATA(ls_zip_entry).

    lo_zipper->get( EXPORTING name    = ls_zip_entry-name
                    IMPORTING content = DATA(lv_data) ).

    DATA(lv_file) = COND #( WHEN ls_zip_entry-name(1) = 'K' THEN p_sapdir && '/cofiles/' && ls_zip_entry-name
                                                            ELSE p_sapdir && '/data/'    && ls_zip_entry-name ).

    TRY.
        OPEN DATASET  lv_file FOR OUTPUT IN BINARY MODE.
        TRANSFER      lv_data TO lv_file.
        CLOSE DATASET lv_file.
      CATCH cx_root INTO DATA(e_text).
        MESSAGE e_text->get_text( ) TYPE 'E'.
    ENDTRY.

  ENDLOOP.


  " now add transport to stms
  DATA lv_ret_code    TYPE trretcode.
  DATA ls_exception   TYPE stmscalert.
  DATA lt_logptr      TYPE TABLE OF tplogptr.
  DATA lt_stdout      TYPE TABLE OF tpstdout.

  DATA(lv_trkorr) = CONV trkorr( lt_zip_entries[ 1 ]-name+8(3) && 'K' && lt_zip_entries[ 1 ]-name+1(6) ).
  DATA(lv_system) = CONV tmssysnam( sy-sysid ).
  SELECT SINGLE domnam FROM tmscsys INTO @DATA(lv_transport_domain).

  " add transport to queue
  CALL FUNCTION 'TMS_MGR_FORWARD_TR_REQUEST'
    EXPORTING
      iv_request     = lv_trkorr
      iv_tarcli      = sy-mandt
      iv_target      = lv_system
      iv_source      = lv_system
      iv_tardom      = lv_transport_domain
      iv_srcdom      = lv_transport_domain
    IMPORTING
      ev_tp_ret_code = lv_ret_code
      es_exception   = ls_exception
    TABLES
      tt_stdout      = lt_stdout
    EXCEPTIONS
      OTHERS         = 99.
  IF sy-subrc <> 0 OR lv_ret_code <> 0.
    cl_demo_output=>display( lt_stdout ).
    MESSAGE 'Could not add transport to queue' TYPE 'E'.
  ENDIF.

  " also directly import if checked
  IF p_import = abap_true.
    CALL FUNCTION 'TMS_MGR_IMPORT_TR_REQUEST'
      EXPORTING
        iv_system                  = lv_system
        iv_request                 = lv_trkorr
        iv_client                  = sy-mandt
        iv_ignore_cvers            = abap_true "ignore invalid component version vector (CVERS)
      IMPORTING
        ev_tp_ret_code             = lv_ret_code
        es_exception               = ls_exception
      TABLES
        tt_logptr                  = lt_logptr
        tt_stdout                  = lt_stdout
      EXCEPTIONS
        read_config_failed         = 1
        table_of_requests_is_empty = 2
        OTHERS                     = 3.
    IF sy-subrc <> 0 OR lv_ret_code <> 0.
      cl_demo_output=>display( lt_stdout ).
      MESSAGE 'Could not import transport' TYPE 'E'.
    ENDIF.
  ENDIF.

  MESSAGE 'Transport successfully imported' TYPE 'S'.

[ABAP] Download Transport as ZIP

Related Reports:
https://nocin.eu/abap-import-transport-from-zip/
https://nocin.eu/abap-create-toc-for-a-given-transport-release-it-and-download-it-as-zip/

This report can be handy, especially since S/4HANA 2023 seems to have restricted the “classic” import way by using TCode CG3Y and CG3Z. See note 1949906, where it is recommended to create a custom report.

*&---------------------------------------------------------------------*
*& Report ZIP_TRANSPORT
*&---------------------------------------------------------------------*
*&
*&---------------------------------------------------------------------*
REPORT zip_transport.

SELECTION-SCREEN BEGIN OF BLOCK bl01 WITH FRAME TITLE TEXT-t01.
PARAMETERS p_trkorr LIKE e070-trkorr OBLIGATORY.
PARAMETERS p_ttext  TYPE as4text.
SELECTION-SCREEN END OF BLOCK bl01.

SELECTION-SCREEN BEGIN OF BLOCK bl02 WITH FRAME TITLE TEXT-t02.
PARAMETERS p_sapdir TYPE string LOWER CASE OBLIGATORY DEFAULT '/usr/sap/trans/'.
PARAMETERS p_lcldir TYPE string LOWER CASE OBLIGATORY DEFAULT 'C:\temp\'.
SELECTION-SCREEN END OF BLOCK bl02.


START-OF-SELECTION.

  " Check if Transport is released
  DATA ls_request TYPE trwbo_request.
  CALL FUNCTION 'TR_READ_REQUEST'
    EXPORTING
      iv_read_e070     = abap_true
      iv_read_e07t     = abap_true
      iv_trkorr        = p_trkorr
    CHANGING
      cs_request       = ls_request
    EXCEPTIONS
      error_occured    = 1
      no_authorization = 2
      OTHERS           = 3.
  IF ls_request-h-trstatus <> 'R'.
    MESSAGE 'Transport not yet released' TYPE 'E'.
  ENDIF.


  " Read released Transport
  DATA lv_xcontent_k TYPE xstring.
  DATA lv_xcontent_r TYPE xstring.

  DATA(lv_transdir_k) = |{ p_sapdir }cofiles/K{ p_trkorr+4 }.{ p_trkorr(3) }|.
  DATA(lv_transdir_r) = |{ p_sapdir }data/R{    p_trkorr+4 }.{ p_trkorr(3) }|.


  TRY.

      " K
      OPEN  DATASET lv_transdir_k FOR INPUT IN BINARY MODE.
      READ  DATASET lv_transdir_k INTO lv_xcontent_k.
      CLOSE DATASET lv_transdir_k.

      " R
      OPEN  DATASET lv_transdir_r FOR INPUT IN BINARY MODE.
      READ  DATASET lv_transdir_r INTO lv_xcontent_r.
      CLOSE DATASET lv_transdir_r.

      " Add to ZIP
      DATA(lo_zipper) = NEW cl_abap_zip( ).

      lo_zipper->add( name    = |K{ p_trkorr+4 }.{ p_trkorr(3) }|
                      content = lv_xcontent_k ).

      lo_zipper->add( name    = |R{ p_trkorr+4 }.{ p_trkorr(3) }|
                      content = lv_xcontent_r ).


      " Download ZIP
      DATA(lv_xzip) = lo_zipper->save( ).

      " Convert to raw data
      DATA(lt_data) = cl_bcs_convert=>xstring_to_solix( iv_xstring = lv_xzip ).

      " Set zip filename
      DATA(lv_zip_name) = COND #( WHEN p_ttext IS INITIAL THEN |{ ls_request-h-as4text }_{ p_trkorr }|
                                                          ELSE |{ p_ttext              }_{ p_trkorr }| ).

      " Replace every character that is not [a-zA-Z0-9_] with '_'.
      REPLACE ALL OCCURRENCES OF REGEX '[^\w]+' IN lv_zip_name WITH '_'.

      cl_gui_frontend_services=>gui_download( EXPORTING filename = p_lcldir && lv_zip_name && '.zip'
                                                        filetype = 'BIN'
                                              CHANGING  data_tab = lt_data ).

    CATCH cx_root INTO DATA(e_text).
      MESSAGE e_text->get_text( ) TYPE 'E'.
  ENDTRY.

  MESSAGE |{ lv_zip_name }.zip created and downloaded to { p_lcldir }| TYPE 'S'.