Additional Blogs by Members
cancel
Showing results for 
Search instead for 
Did you mean: 
Former Member
0 Kudos

The Problem


     : I need to develop a tutorial to be published on my personal website. Unfortunately, my personal website
               being free-hosted, can't afford heavy images generated
               using print-screen for Z transactions. It should work on MiniSAP - SAP Release 6.10 (Basis/ABA) [ Who cares


about the rest of the world :wink: ]
 


Other Benefits : Unlike print-screen
    • HTML pages are scrollable and light.
    • Also there will not be any resolution related problems as in case of images.
    • Users can cut & paste the data from HTML Screen , if required.
    • The downloaded SCREEN-HTML can be used for documentation
      purpose and for sharing it over the web.
    • At times SAP Users demand for exact Print of Screens
      rather than a List. This utility, being generic, can be
      used to enable PRINT facility for simple transactions.


Requirement

: The attempt is to provide
               "Print-Screen to HTML" functionality for simple SAP
               Transaction Screens .
               This function module can be called
               at 'Print' command for the current screen.
               It will generate a HTML file to display simple SAP
               Transaction screens ( Fields with Contents ) as HTML.
               The functionality should be generic in nature and
               re-usable for other transactions.
  





Processing :


    1. The function module Z_RMTIWARI_PRINTSCREEN_TO_HTML is called, in the PAI of the screen to be printed,
      at command for 'Print'.

     CASE sy-ucomm.
*.......
     WHEN 'PRINT'.
      data : lv_program type sy-repid,
             lv_dynnr   type sy-dynnr.


             lv_program =  sy-repid.
             lv_dynnr   = sy-dynnr.


      CALL FUNCTION 'Z_RMTIWARI_PRINTSCREEN_TO_HTML'
        EXPORTING
          PROGRAM       = lv_program
          DYNPRO        = lv_dynnr.
  • .......


  •     ENDCASE.


                      
                  
    1. This FM 'Z_RMTIWARI_PRINTSCREEN_TO_HTML'
      first generates HTML code for a blank
      screen-display of current screen. This is achieved by
      submitting a program Z_RMTIWARI_PRINTSCREEN_TO_HTML
      which in turn calls FM 'RS_SCRP_PRINT_IN_LIST'
      for the transaction screen. The program generates a
      spool for a simple list of the blank Screen [ Only the field name
      and blank input/output fields ].
    2. This list will be read using FM LIST_FROM_MEMORY. Further, it will be converted into HTML.
      Also the field-values needs to
      be supplemented in the subsequent processing.

    3. FM 'WWW_HTML_FROM_LISTOBJECT' is used to convert List to
      HTML and further actual field values, retrieved using
      'DYNP_VALUES_READ', are imposed on the generated
      HTML and downloaded to the local folder. The final HTML file displays a screen similar to
      SAPGui Xn screen including the field values.


Result :



It seems IFRAMEs can't be used here. Also, I tried pasting the html code directly but SDN's weblog is not able to show it properly. So no other go...


Check this link to see the result page:
Result Screen






Function Module :



FUNCTION Z_RMTIWARI_PRINTSCREEN_TO_HTML.
*"----
""Local interface:
*"  IMPORTING
*"     REFERENCE(PROGRAM) TYPE  SY-REPID
*"     REFERENCE(DYNPRO) TYPE  SY-DYNNR
*"  EXCEPTIONS
*"      DOWNLOAD_ERROR
*"----
  • Written By : Ram Manohar Tiwari
*
  • Problem    : I need to develop a tutorial to be published on my
  •               personal website. Unfortunately my personal website
  •               being free-hosted, can't afford heavy images created
  •               using print-screen for Z transactions.
*
  • Function   : The attempt is to provide
  •               "Print-Screen to HTML" functionality for simple SAP
  •               Transaction Screens .
  •               This function module can be called
  •               at 'Print' command for the current screen.
  •               It will generate a HTML file to display simple SAP
  •               Transaction screens ( Fields with Contents ) as HTML.
  •               The functionality should be generic in nature and
  •               re-usable for other transactions.
*
  • Other Benifits : Unlike print-screen the HTML pages are scrollable and
  •               light. Also there will not be any resolution related
  •               problems as in case of images. Further, users can
  •               cut & paste the data from HTML Screen , if required.
  •               The downloaded SCREEN-HTML can be used for documentation
  •               purpose and for sharing it over the web.
  •               At times SAP Users demand for exact Print of Screens
  •               rather than a List. This utility, being generic, can be
  •               used to enable PRINT facility for simple transactions.
*
  • Processing : This FM first generates HTML code for a blank
  •               screen-display of current screen. This is achieved by
  •               submitting a program Z_RMTIWARI_PRINTSCREEN_TO_HTML
  •               which in turn calls FM 'RS_SCRP_PRINT_IN_LIST'
  •               for the transaction screen. This program generates a
  •               simple list for the blank Screen [ Only the field name
  •               and blank input/output fields ]. Further this list
  •               requires to be converted into HTML and values needs to
  •               be supplemented in the subsequent processing.
  •               FM 'WWW_HTML_FROM_LISTOBJECT' is used to convert List to
  •               HTML and further actual field values, retrived using
  •               'DYNP_VALUES_READ', are imposed on the generated
  •               HTML. The final HTML file displays a screen similar to
  •               SAPGui Xn screen including the field values.
*"----


      DATA: lv_dynpname TYPE TSTC-PGMNA,
            lv_dynpnumb TYPE TSTC-DYPNO.


      DATA: BEGIN OF lt_dynpvaluetab OCCURS 1.
              INCLUDE STRUCTURE dynpread.
      DATA: END   OF lt_dynpvaluetab.


      DATA: lt_dyn_fields TYPE standard table of RSDCF with header line,
            lt_lines      TYPE standard table of TLINE with header line.


      DATA: lt_abap_list LIKE abaplist OCCURS 1.
      DATA: BEGIN OF lt_html_tab OCCURS 0.
              INCLUDE STRUCTURE w3html.
      DATA: END OF lt_html_tab.
      DATA: lv_html_tab_wide(50000) type c.


      DATA: BEGIN OF lt_html_tab_str OCCURS 0,
              line type string.
      DATA: END OF lt_html_tab_str.
      DATA: lt_icontab(32) OCCURS 10 WITH HEADER LINE.
----

      TYPE-POOLS: sbdst.


      DATA: lineno TYPE i, length TYPE i, size TYPE i.
      DATA: icon_wa  TYPE icon,
            internal TYPE icon-internal,
            existing TYPE c.
      DATA: my_bds TYPE REF TO cl_bds_document_set,
            key    TYPE sbdst_object_key,
            files  TYPE sbdst_files,
            wa     TYPE bapifiles.
      data: filename type string,
            filefilter type string,
            path type string,
            fullpath type string.
      data: user_action type i.
      data: cur_guicopdepage(4) type n.


----


  •     Get Data Fields of current Screen.
      lv_dynpname =  program.
      lv_dynpnumb =  dynpro.


      CALL FUNCTION 'DYNPRO_FIELD_GET'
        EXPORTING
          DYNPRO           = lv_dynpnumb
          PROGRAM          = lv_dynpname
        TABLES
          DYNP_FIELDS      = lt_dyn_fields
          LINES            = lt_lines
        EXCEPTIONS
          DYNPRO_NOT_FOUND = 1
          OTHERS           = 2.
      IF SY-SUBRC <> 0.
  • MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
  •         WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
      ENDIF.


      REFRESH lt_dynpvaluetab.
      LOOP AT lt_dyn_fields.
        check not lt_dyn_fields-fldname is initial.
        lt_dynpvaluetab-fieldname = lt_dyn_fields-DYNPRO_FLD.
        APPEND lt_dynpvaluetab.
      ENDLOOP.


  DATA: lv_dynpname1 TYPE D020S-PROG,
        lv_dynpnumb1 TYPE D020S-DNUM.
.
      lv_dynpname1 = program.
      lv_dynpnumb1 = dynpro.
.
  •     Read values of data-fields on the current screen.
      CALL FUNCTION 'DYNP_VALUES_READ'
        EXPORTING
          dyname               = lv_dynpname1
          dynumb               = lv_dynpnumb1
        TABLES
          dynpfields           = lt_dynpvaluetab
        EXCEPTIONS
          invalid_abapworkarea = 1
          invalid_dynprofield  = 2
          invalid_dynproname   = 3
          invalid_dynpronummer = 4
          invalid_request      = 5
          no_fielddescription  = 6
          invalid_parameter    = 7
          undefind_error       = 8
          double_conversion    = 9
          OTHERS               = 10.
      IF sy-subrc = 0.


      ENDIF.


  •     Call program and then get the list from memory.
  •     This program generates a simple list for the blank Screen
  •     .
  •     Further values needs to be supplemented in the subsequent
  •     processing.
      SUBMIT Z_RMTIWARI_PRINTSCREEN_TO_HTML AND RETURN
      WITH P_PROG  eq program
      WITH P_DYNNR eq DYNPRO
      EXPORTING LIST TO MEMORY.


      CALL FUNCTION 'LIST_FROM_MEMORY'
        TABLES
          LISTOBJECT       = lt_abap_list
  •   EXCEPTIONS
  •     NOT_FOUND        = 1
  •     OTHERS           = 2
                .
      IF SY-SUBRC <> 0.
  • MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
  •         WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
      ENDIF.


      CALL FUNCTION 'WWW_HTML_FROM_LISTOBJECT'
           EXPORTING
  •               REPORT_NAME   =
                template_name = 'WEBREPORTING_REPORT'
           TABLES
                html          =  lt_html_tab
                listobject    =  lt_abap_list
                listicons     =  lt_icontab.
  • for UNICODE Systems we need a new type of DOWNLOAD: table-lines of
  • html_table must be downloaded without end-marks or blanks between the
  • lines (still to be developed!, the same problem as with EBCDIC)
      DESCRIBE TABLE lt_html_tab LINES lineno .
      DESCRIBE FIELD lt_html_tab LENGTH length in byte mode.
      size = length * lineno.


      data : lv_row type sy-tabix,
             lv_text_pos type sy-fdpos.
      field-symbols : type any.
      data : lv_count type i,
             lv_char type c,
             lv_replace_str(200) type C,
             lv_field_length type i,
             lv_value_length type i.


     LOOP AT lt_html_tab.
      TRANSLATE lt_html_tab using ' *'.
      CONCATENATE lv_html_tab_wide lt_html_tab  into lv_html_tab_wide.


     ENDLOOP.


  •      lt_html_tab_wide[] = lt_html_tab[].


       TRANSLATE lv_html_tab_wide using '* '.


  •       Step below is to overwrite the blank input / outputs fields
  •       retrived in the last step with actual runtime values of those
  •       fields.
        LOOP AT lt_dynpvaluetab.
          READ TABLE lt_dyn_fields
          with key DYNPRO_FLD = lt_dynpvaluetab-FIELDNAME.
          check sy-subrc eq 0.


          SEARCH lv_html_tab_wide FOR lt_dyn_fields-stxt1 .
          check sy-subrc eq 0.
          lv_row = 1. "sy-tabix.
          lv_text_pos = sy-fdpos.
  •          READ TABLE lt_html_tab_wide index lv_row.
  •          check sy-subrc eq 0.
          search lv_html_tab_wide FOR '_' . "STARTING AT lv_text_pos.
          check sy-subrc eq 0.
  •          assign (lt_dynpvaluetab-FIELDNAME) to <fs>.
  •          <fs> = lt_dynpvaluetab-FIELDVALUE.
          CONDENSE lt_dynpvaluetab-FIELDVALUE.
          lv_count = sy-fdpos.
          clear lv_replace_str.
          DO 50 times.
            if lv_count eq 50000.
              exit.
            endif.
            lv_char = lv_html_tab_wide+lv_count(1).
            if lv_char eq '_'.
              lv_count = lv_count + 1.
              concatenate '_' lv_replace_str into lv_replace_str .
            else.
              EXIT.
            ENDIF.
          ENDDO.


         IF lt_dynpvaluetab-FIELDVALUE CO ' 0123456789'.
         lv_field_length = strlen( lv_replace_str ).
         lv_value_length = strlen( lt_dynpvaluetab-FIELDVALUE ).


         if lv_field_length ne lv_value_length.
            lv_field_length = ( lv_field_length - lv_value_length ).
            DO lv_field_length times.
             CONCATENATE '0' lt_dynpvaluetab-FIELDVALUE
                    into lt_dynpvaluetab-FIELDVALUE.
            ENDDO.
         endif.
         endif.


          REPLACE lv_replace_str IN lv_html_tab_wide
          with lt_dynpvaluetab-FIELDVALUE.
  •          REPLACE ALL occurrences OF '_' in lt_html_tab
  •          with ' '.


    •          REPLACE SECTION OFFSET sy-fdpos length 1 OF lt_html_tab
  •             WITH lt_dynpvaluetab-FIELDVALUE.
  •          check sy-subrc eq 0.
  •          MODIFY lt_html_tab_wide index lv_row.
        ENDLOOP.


        REFRESH lt_html_tab[].


  •      DESCRIBE TABLE lt_html_tab_wide LINES lineno .
  •      DESCRIBE FIELD lt_html_tab_wide LENGTH length in byte mode.
  •      size = length * lineno.


  •      For the time-being limit of downloaded file size is set to 20000.
       CALL FUNCTION 'IQAPI_WORD_WRAP'
         EXPORTING
           TEXTLINE                  = lv_html_tab_wide
  •          DELIMITER                 = ' '
           OUTPUTLEN                 = 255
  •        IMPORTING
  •          OUT_LINE1                 =
  •          OUT_LINE2                 =
  •          OUT_LINE3                 =
         TABLES
           OUT_LINES                 = lt_html_tab
  •        EXCEPTIONS
  •          OUTPUTLEN_TOO_LARGE       = 1
  •          OTHERS                    = 2
                 .
       IF SY-SUBRC <> 0.
  • MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
  •         WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
       ENDIF.


*
  •       size = 20000.
  •      data : lv_pos1 type i.
  •      DO 80 times.
  •        lt_html_tab = lv_html_tab_wide+lv_pos1(255).
  •        lv_pos1 = lv_pos1 + 255.
  •        APPEND lt_html_tab.
*
  •        SEARCH lt_html_tab for '</html>'.
  •        if sy-subrc eq 0.
  •         exit.
  •        endif.
  •      ENDDO.


  •     Save HTML File
      concatenate text-ht1 '|' into filefilter.
      call method CL_GUI_FRONTEND_SERVICES=>FILE_SAVE_DIALOG
        EXPORTING
          file_filter = filefilter
        CHANGING
          filename    = filename
          path        = path
          fullpath    = fullpath
          user_action = user_action.


       if user_action = CL_GUI_FRONTEND_SERVICES=>ACTION_OK.
        call 'CUR_LCL' id 'GUICP'  field cur_guicopdepage.
        loop at lt_html_tab.
          call function 'SCP_TRANSLATE_CHARS'
            EXPORTING
              inbuff           = lt_html_tab
              outcode          = cur_guicopdepage
              csubst           = 'X'
              substc_space     = 'X'
            IMPORTING
              outbuff          = lt_html_tab
            EXCEPTIONS
              invalid_codepage = 1
              internal_error   = 2
              cannot_convert   = 3
              fields_bad_type  = 4
              others           = 5.
          if sy-subrc <> 0.
            message i020(02) raising download_error.
          endif.
          modify lt_html_tab.
        endloop.


        CALL FUNCTION 'GUI_DOWNLOAD'
          EXPORTING
            filename     = fullpath
            FILETYPE     = 'ASC'
  •            bin_filesize = size
            TRUNC_TRAILING_BLANKS = 'X'
          TABLES
            DATA_TAB     = lt_html_tab
          EXCEPTIONS
            OTHERS       = 99.
        if sy-subrc <> 0.
          MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
                 RAISING DOWNLOAD_ERROR.
        endif.
      endif.


  • download of SAP icons appearing in the list
      LOOP AT lt_icontab.
  • no icon download if icon already exists in directory
        CONCATENATE path lt_icontab '.gif' INTO filename.
        call method CL_GUI_FRONTEND_SERVICES=>FILE_EXIST
          EXPORTING
            file   = filename
          RECEIVING
            result = existing.


        IF existing is initial.
  • icon not there -> download from BDS
          IF my_bds IS INITIAL.
            CREATE OBJECT my_bds.
          ENDIF.
          TRANSLATE lt_icontab TO UPPER CASE.               "#EC
          "SYNTCHAR
          CONCATENATE '@' lt_icontab+2 '@' INTO internal.
          SELECT SINGLE * FROM icon INTO icon_wa
                                          WHERE internal = internal.
          key =  icon_wa-name .
          wa-comp_count = 1.
          wa-directory = path.
          wa-mimetype = 'IMAGE/GIF'.
          APPEND wa TO files.
          CALL METHOD my_bds->get_with_files
            EXPORTING
              classname  = 'SAP_ICONS'
              classtype  = 'OT'
              object_key = key
            CHANGING
              files      = files
            EXCEPTIONS
              OTHERS     = 1.
          IF sy-subrc NE 0.
            MESSAGE i004(02) WITH key
            'Problem in getting ICON Files from BDS'.
          ENDIF.
          CLEAR files.
        ENDIF.
      ENDLOOP.


ENDFUNCTION.
    

Program :



&----

*& Report  Z_RMTIWARI_PRINTSCREEN_TO_HTML                              *
*&                                                                     *
&----

*& Written By : Ram Manohar Tiwari                                     *
*& Function   : It can print a spool-list for the specified Screen     *
&----


REPORT  Z_RMTIWARI_PRINTSCREEN_TO_HTML          .
PARAMETERS : P_PROG     LIKE d020s-prog OBLIGATORY.
PARAMETERS : P_DYNNR(4) TYPE C          OBLIGATORY.
SET LANGUAGE 'EN'..


CALL FUNCTION 'RS_SCRP_PRINT_IN_LIST'
  EXPORTING
    ATTRIBS         = ' '
    DYNNR           = P_DYNNR
    FIELDS          = ' '
    FULLSCR         = 'X'
    LOGIC           = ' '
    PROGNAME        = P_PROG
  •   TRANS           = ' '
  • EXCEPTIONS
  •   CANCELLED       = 1
  •   NOT_FOUND       = 2
  •   OTHERS          = 3
          .
IF SY-SUBRC <> 0.
  • MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
  •         WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
ENDIF.


Conclusion:


As you must have figured it out by now ...it's useless...well almost :wink:
1 Comment