*&---------------------------------------------------------------------*
*& Report  ZDB_DOWNLOAD_R3_46                                          *
*&                                                                     *
*&---------------------------------------------------------------------*
*&                                                                     *
*& This program is free software: you can redistribute it and/or       *
*& modify it under the terms of the GNU General Public License as      *
*& published by the Free Software Foundation, either version 3 of the  *
*& License, or any later version.                                      *
*&                                                                     *
*& This program is distributed in the hope that it will be useful,     *
*& but WITHOUT ANY WARRANTY; without even the implied warranty of      *
*& MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.                *
*& See the GNU General Public License for more details.                *
*&                                                                     *
*& You should have received a copy of the GNU General Public License   *
*& along with this program. If not, see <http://www.gnu.org/licenses/>.*
*&                                                                     *
*&---------------------------------------------------------------------*
*&                                                                     *
*&  Author:     Ruediger von Creytz     ruediger.creytz@globalbit.net  *
*&  Copyright:  globalBIT, LLC          http://www.globalbit.net       *
*&  Version:    20210302                                               *
*&                                                                     *
*&---------------------------------------------------------------------*

REPORT  zdb_download_r3_46                            .

*&---------------------------------------------------------------------*
*&  Include           ZDB_DOWNLOAD_VARIABLES                           *
*&                                                                     *
*&---------------------------------------------------------------------*
*&                                                                     *
*& This file is part of ZDB.                                           *
*&                                                                     *
*& ZDB_DOWNLOAD is free software: you can redistribute it and/or       *
*& modify it under the terms of the GNU General Public License as      *
*& published by the Free Software Foundation, either version 3 of the  *
*& License, or any later version.                                      *
*&                                                                     *
*& ZDB_DOWNLOAD is distributed in the hope that it will be useful,     *
*& but WITHOUT ANY WARRANTY; without even the implied warranty of      *
*& MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
*& GNU General Public License for more details.                        *
*&                                                                     *
*& You should have received a copy of the GNU General Public License   *
*& along with ZDOWNLOAD. If not, see <http://www.gnu.org/licenses/>.   *
*&                                                                     *
*&---------------------------------------------------------------------*
*&                                                                     *
*&  Author:     Ruediger von Creytz     ruediger.creytz@globalbit.net  *
*&  Copyright:  globalBIT, LLC          http://www.globalbit.net       *
*&                                                                     *
*&---------------------------------------------------------------------*


TYPE-POOLS:
abap.

TYPES:
it_string TYPE STANDARD TABLE OF string.

DATA:
gt_tadir TYPE STANDARD TABLE OF tadir,
g_folder TYPE string,
g_add_db_format_csv   TYPE flag      VALUE abap_true,
g_add_db_format_xml   TYPE flag      VALUE abap_true,
g_add_db_max_lines    TYPE i         VALUE 500.

CONSTANTS:
gc_extension_csv     TYPE char3     VALUE 'csv',
gc_extension_xml     TYPE char3     VALUE 'xml'.

TABLES:
dd02l,
tdevc.
*&---------------------------------------------------------------------*
*&  Include           ZDB_DOWNLOAD_CONVERT_DATA                        *
*&                                                                     *
*&---------------------------------------------------------------------*
*&                                                                     *
*& This file is part of ZDB.                                           *
*&                                                                     *
*& ZDB_DOWNLOAD is free software: you can redistribute it and/or       *
*& modify it under the terms of the GNU General Public License as      *
*& published by the Free Software Foundation, either version 3 of the  *
*& License, or any later version.                                      *
*&                                                                     *
*& ZDB_DOWNLOAD is distributed in the hope that it will be useful,     *
*& but WITHOUT ANY WARRANTY; without even the implied warranty of      *
*& MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
*& GNU General Public License for more details.                        *
*&                                                                     *
*& You should have received a copy of the GNU General Public License   *
*& along with ZDOWNLOAD. If not, see <http://www.gnu.org/licenses/>.   *
*&                                                                     *
*&---------------------------------------------------------------------*
*&                                                                     *
*&  Author:     Ruediger von Creytz     ruediger.creytz@globalbit.net  *
*&  Copyright:  globalBIT, LLC          http://www.globalbit.net       *
*&                                                                     *
*&---------------------------------------------------------------------*


*-----------------------------------------------------------------------
* form: data2csv
*-----------------------------------------------------------------------
FORM data2csv USING
                value(i_tabname)
              CHANGING
                ct_csv TYPE it_string.
  DATA:
  lt_dd03l TYPE STANDARD TABLE OF dd03l,
  ls_dd02l TYPE dd02l,
  l_fieldname TYPE fieldname,
  l_position TYPE tabfdpos,
  l_value TYPE string,
  l_csv TYPE string,
  l_len TYPE i,
  l_length TYPE string,
  ls_fs TYPE REF TO data.

  FIELD-SYMBOLS:
  <ls_dd03l> TYPE dd03l,
  <ls_fs> TYPE ANY,
  <l_value> TYPE ANY.

  REFRESH ct_csv.

  SELECT * FROM dd03l INTO TABLE lt_dd03l
      WHERE tabname = i_tabname
      AND as4local = 'A'
      ORDER BY position.

  SELECT SINGLE * FROM dd02l INTO ls_dd02l
      WHERE tabname = i_tabname
      AND as4local = 'A'.

  LOOP AT lt_dd03l ASSIGNING <ls_dd03l>.
    IF <ls_dd03l>-fieldname+0(1) = '.'.
      CONTINUE.
    ENDIF.
    IF NOT l_csv IS INITIAL.
      CONCATENATE l_csv ';' INTO l_csv.
    ENDIF.
    l_len = <ls_dd03l>-intlen.
    l_length = l_len.
    CONDENSE l_length.
    CONCATENATE l_csv '"' <ls_dd03l>-fieldname
      '(' <ls_dd03l>-inttype l_length ')"'
      INTO l_csv.
  ENDLOOP.
  APPEND l_csv TO ct_csv.

*content
  CREATE DATA ls_fs TYPE (i_tabname).
  ASSIGN ls_fs->* TO <ls_fs>.
  SELECT * FROM (i_tabname) INTO <ls_fs>.
    CLEAR l_csv.
    LOOP AT lt_dd03l ASSIGNING <ls_dd03l>.
      CLEAR l_value.
      IF <ls_dd03l>-fieldname+0(1) = '.'.
        CONTINUE.
      ENDIF.

      IF NOT <ls_dd03l>-datatype = 'RAWSTRING'.
        ASSIGN COMPONENT <ls_dd03l>-fieldname OF STRUCTURE <ls_fs>
            TO <l_value>.
        l_value = <l_value>.
      ENDIF.

      IF NOT l_csv IS INITIAL.
        CONCATENATE l_csv ';' INTO l_csv.
      ENDIF.
      CONCATENATE l_csv '"' l_value '"' INTO l_csv.
    ENDLOOP.
    APPEND l_csv TO ct_csv.
    IF sy-dbcnt = g_add_db_max_lines.
      EXIT.
    ENDIF.
  ENDSELECT.

ENDFORM.                    "select_data2csv


*-----------------------------------------------------------------------
* form: data2xml
*-----------------------------------------------------------------------
FORM data2xml USING
                value(i_tabname)
              CHANGING
                ct_xml TYPE it_string.
  DATA:
  lt_dd03l TYPE STANDARD TABLE OF dd03l,
  ls_dd03t TYPE dd03t,
  ls_dd02l TYPE dd02l,
  ls_dd02t TYPE dd02t,
  l_fieldname(30) TYPE c,
  l_position TYPE tabfdpos,
  l_value TYPE string,
  l_xml TYPE string,
  ls_fs TYPE REF TO data.

  FIELD-SYMBOLS:
  <ls_dd03l> TYPE dd03l,
  <ls_fs> TYPE ANY,
  <l_value> TYPE ANY.

  REFRESH ct_xml.

  SELECT * FROM dd03l INTO TABLE lt_dd03l
      WHERE tabname = i_tabname
      AND as4local = 'A'
      ORDER BY position.

  APPEND '<?xml version="1.0" encoding="UTF-8" ?>' TO ct_xml.
  APPEND '<db>' TO ct_xml.
  APPEND '<definition><table>' TO ct_xml.
  SELECT SINGLE * FROM dd02l INTO ls_dd02l
    WHERE tabname = i_tabname
    AND as4local = 'A'.
  SELECT fieldname position FROM dd03l INTO (l_fieldname, l_position)
      WHERE tabname = 'DD02L'
      ORDER BY position.
    ASSIGN COMPONENT l_fieldname OF STRUCTURE ls_dd02l
        TO <l_value>.
    IF NOT <l_value> IS INITIAL.
      l_value = <l_value>.
      PERFORM encode_html CHANGING l_value.
      TRANSLATE l_fieldname TO LOWER CASE.
      CONCATENATE
        '<' l_fieldname ' value="' l_value '"/>'
        INTO l_xml.
      APPEND l_xml TO ct_xml.
    ENDIF.
  ENDSELECT.

  SELECT * FROM dd02t INTO ls_dd02t
      WHERE tabname = i_tabname
      AND as4local = 'A'.
    CONCATENATE
      '<text language="' ls_dd02t-ddlanguage '">'
      ls_dd02t-ddtext
      '</text>'
      INTO l_xml.
    APPEND l_xml TO ct_xml.
  ENDSELECT.

  APPEND '</table>' TO ct_xml.

  LOOP AT lt_dd03l ASSIGNING <ls_dd03l>.
    IF <ls_dd03l>-fieldname+0(1) = '.'.
      CONTINUE.
    ENDIF.
    APPEND '<col>' TO ct_xml.
    SELECT fieldname position FROM dd03l INTO (l_fieldname, l_position)
        WHERE tabname = 'DD03L'
        AND fieldname <> 'TABNAME'
        ORDER BY position.
      ASSIGN COMPONENT l_fieldname OF STRUCTURE <ls_dd03l>
        TO <l_value>.
      l_value = <l_value>.
      IF NOT <l_value> IS INITIAL.
        PERFORM encode_html CHANGING l_value.
        TRANSLATE l_fieldname TO LOWER CASE.
        CONCATENATE
            '<' l_fieldname '>' l_value '</' l_fieldname '>'
            INTO l_xml.
        APPEND l_xml TO ct_xml.
      ENDIF.
    ENDSELECT.
    SELECT * FROM dd03t INTO ls_dd03t
        WHERE tabname = <ls_dd03l>-tabname
        AND fieldname = <ls_dd03l>-fieldname
        AND as4local = 'A'.
      CONCATENATE
        '<text language="' ls_dd03t-ddlanguage '">'
        ls_dd03t-ddtext
        '</text>'
        INTO l_xml.
      APPEND l_xml TO ct_xml.
    ENDSELECT.
    APPEND '</col>' TO ct_xml.
  ENDLOOP.

  APPEND '</definition>' TO ct_xml.

*content
  APPEND '<lines>' TO ct_xml.

  CREATE DATA ls_fs TYPE (i_tabname).
  ASSIGN ls_fs->* TO <ls_fs>.
  SELECT * FROM (i_tabname) INTO <ls_fs>.
    CLEAR l_xml.

    APPEND '<line>' TO ct_xml.

    LOOP AT lt_dd03l ASSIGNING <ls_dd03l>.
      IF <ls_dd03l>-fieldname+0(1) = '.'.
        CONTINUE.
      ENDIF.
      CLEAR l_value.
      IF NOT <ls_dd03l>-datatype = 'RAWSTRING'.
        ASSIGN COMPONENT <ls_dd03l>-fieldname OF STRUCTURE <ls_fs>
            TO <l_value>.
        l_value = <l_value>.
        PERFORM encode_html CHANGING l_value.
      ENDIF.

      IF NOT <l_value> IS INITIAL.
        IF <ls_dd03l>-fieldname(1) = '.'.
          <ls_dd03l>-fieldname(1) = '_'.
        ENDIF.
        CONCATENATE
            '<cell name="' <ls_dd03l>-fieldname '">'
            l_value
            '</cell>' INTO l_xml.
        APPEND l_xml TO ct_xml.
      ENDIF.
    ENDLOOP.
    APPEND '</line>' TO ct_xml.
    IF sy-dbcnt = g_add_db_max_lines.
      EXIT.
    ENDIF.
  ENDSELECT.
  APPEND '</lines></db>' TO ct_xml.

ENDFORM.                    "select_data2xml
*&---------------------------------------------------------------------*
*&  Include           ZDB_DOWNLOAD_DO                                  *
*&                                                                     *
*&---------------------------------------------------------------------*
*&                                                                     *
*& This file is part of ZDB.                                           *
*&                                                                     *
*& ZDB_DOWNLOAD is free software: you can redistribute it and/or       *
*& modify it under the terms of the GNU General Public License as      *
*& published by the Free Software Foundation, either version 3 of the  *
*& License, or any later version.                                      *
*&                                                                     *
*& ZDB_DOWNLOAD is distributed in the hope that it will be useful,     *
*& but WITHOUT ANY WARRANTY; without even the implied warranty of      *
*& MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
*& GNU General Public License for more details.                        *
*&                                                                     *
*& You should have received a copy of the GNU General Public License   *
*& along with ZDOWNLOAD. If not, see <http://www.gnu.org/licenses/>.   *
*&                                                                     *
*&---------------------------------------------------------------------*
*&                                                                     *
*&  Author:     Ruediger von Creytz     ruediger.creytz@globalbit.net  *
*&  Copyright:  globalBIT, LLC          http://www.globalbit.net       *
*&                                                                     *
*&---------------------------------------------------------------------*


*-----------------------------------------------------------------------
* form: download
*-----------------------------------------------------------------------
FORM download USING
                value(i_pack)
                value(i_tabname)
                value(i_extension)
                it_string TYPE it_string.

  DATA:
  l_infoline(80),
  l_uri TYPE string.

  PERFORM getfilename USING i_pack i_tabname i_extension
                      CHANGING l_uri.

  CALL FUNCTION 'GUI_DOWNLOAD'
    EXPORTING
      filename = l_uri
    TABLES
      data_tab = it_string
    EXCEPTIONS
      OTHERS   = 1.

  IF sy-subrc <> 0.
    CONCATENATE i_tabname '.' i_extension
      INTO l_infoline.
    CONCATENATE
      text-010 l_infoline
      INTO l_infoline SEPARATED BY space.
    WRITE: l_infoline, sy-subrc.
  ENDIF.

ENDFORM.                    "download


*-----------------------------------------------------------------------
* form: getFilename
*-----------------------------------------------------------------------
FORM getfilename USING
                   value(i_pack)
                   value(i_tabname)
                   value(i_extension)
                 CHANGING
                   c_uri TYPE string.

  DATA:
  f_infoline(80),
  f_delimiter TYPE string VALUE '\',
  f_dbl_delimiter TYPE string VALUE '\\'.

  CONCATENATE i_tabname '.' i_extension
    INTO f_infoline.
  CONCATENATE
      text-009 f_infoline
      INTO f_infoline SEPARATED BY space.

  CALL FUNCTION 'SAPGUI_PROGRESS_INDICATOR'
    EXPORTING
      text = f_infoline.

  CONCATENATE
      g_folder
      f_delimiter i_pack
      f_delimiter 'R3TR_TABL'
      f_delimiter i_tabname
      '.' i_extension
      INTO c_uri.
  PERFORM replace_all
    USING '/' f_delimiter
    CHANGING c_uri.
  WHILE c_uri CS f_dbl_delimiter.
    PERFORM replace_all
      USING f_dbl_delimiter f_delimiter
      CHANGING c_uri.
  ENDWHILE.

ENDFORM.                    "getFilename
*&---------------------------------------------------------------------*
*&  Include           ZDB_DOWNLOAD_GUI                                 *
*&                                                                     *
*&---------------------------------------------------------------------*
*&                                                                     *
*& This file is part of ZDB.                                           *
*&                                                                     *
*& ZDB_DOWNLOAD is free software: you can redistribute it and/or       *
*& modify it under the terms of the GNU General Public License as      *
*& published by the Free Software Foundation, either version 3 of the  *
*& License, or any later version.                                      *
*&                                                                     *
*& ZDB_DOWNLOAD is distributed in the hope that it will be useful,     *
*& but WITHOUT ANY WARRANTY; without even the implied warranty of      *
*& MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
*& GNU General Public License for more details.                        *
*&                                                                     *
*& You should have received a copy of the GNU General Public License   *
*& along with ZDOWNLOAD. If not, see <http://www.gnu.org/licenses/>.   *
*&                                                                     *
*&---------------------------------------------------------------------*
*&                                                                     *
*&  Author:     Ruediger von Creytz     ruediger.creytz@globalbit.net  *
*&  Copyright:  globalBIT, LLC          http://www.globalbit.net       *
*&                                                                     *
*&---------------------------------------------------------------------*


*-----------------------------------------------------------------------
*  Selection screen declaration
*-----------------------------------------------------------------------
SELECTION-SCREEN BEGIN OF BLOCK b1 WITH FRAME TITLE t_choice.
* Package
SELECTION-SCREEN BEGIN OF LINE.
SELECTION-SCREEN COMMENT 1(22) t_pack.
SELECT-OPTIONS p_pack FOR tdevc-devclass.
SELECTION-SCREEN END OF LINE.
* Database
SELECTION-SCREEN BEGIN OF LINE.
SELECTION-SCREEN COMMENT 1(22) t_db.
SELECT-OPTIONS p_db FOR dd02l-tabname.
SELECTION-SCREEN END OF LINE.
*Folder
SELECTION-SCREEN ULINE.
SELECTION-SCREEN BEGIN OF LINE.
SELECTION-SCREEN COMMENT 1(25) t_path.
PARAMETERS: p_folder LIKE rlgrap-filename MEMORY ID mfolder.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN: END OF BLOCK b1.

SELECTION-SCREEN: BEGIN OF BLOCK b2 WITH FRAME TITLE t_opts.
SELECTION-SCREEN BEGIN OF LINE.
SELECTION-SCREEN COMMENT 1(25) t_format.
PARAMETERS p_csv AS CHECKBOX DEFAULT abap_true.
SELECTION-SCREEN COMMENT 29(15) t_csv.
PARAMETERS p_xml AS CHECKBOX DEFAULT abap_true.
SELECTION-SCREEN COMMENT 47(15) t_xml.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN BEGIN OF LINE.
SELECTION-SCREEN COMMENT 1(25) t_max.
PARAMETERS p_max TYPE i DEFAULT 500.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN: END OF BLOCK b2.


*-----------------------------------------------------------------------
* Display a directory picker window
*-----------------------------------------------------------------------
AT SELECTION-SCREEN ON VALUE-REQUEST FOR p_folder.

  DATA:
  s_obj_file TYPE REF TO cl_gui_frontend_services,
  s_picked_folder TYPE string,
  s_initial_folder TYPE string.

  IF sy-batch IS INITIAL.
    CREATE OBJECT s_obj_file.

    IF NOT p_folder IS INITIAL.
      s_initial_folder = p_folder.
    ELSE.
      CALL METHOD s_obj_file->get_temp_directory
        CHANGING
          temp_dir = s_initial_folder
        EXCEPTIONS
          OTHERS   = 1.
    ENDIF.

    CALL METHOD s_obj_file->directory_browse
      EXPORTING
        initial_folder  = s_initial_folder
      CHANGING
        selected_folder = s_picked_folder
      EXCEPTIONS
        OTHERS          = 1.

    IF sy-subrc = 0.
      p_folder = s_picked_folder.
    ELSE.
      WRITE: / text-001.
    ENDIF.
  ENDIF.


*-----------------------------------------------------------------------
*  Initialization
*-----------------------------------------------------------------------
INITIALIZATION.
* screen texts
  t_choice = 'Choice'.
  t_csv    = gc_extension_csv.
  t_db     = 'Database'.
  t_format = 'Format'.
  t_max    = 'Max. no. of lines'.
  t_opts   = 'Options'.
  t_pack   = 'Package'.
  t_path   = 'Directory'.
  t_xml    = gc_extension_xml.


*-----------------------------------------------------------------------
* start-of-selection
*-----------------------------------------------------------------------
START-OF-SELECTION.
  DATA:
  lt_tadir TYPE STANDARD TABLE OF tadir,
  l_tabname TYPE tabname.

  FIELD-SYMBOLS:
  <ls_tadir> TYPE tadir.

  CLEAR:
  g_folder,
  g_add_db_format_csv,
  g_add_db_format_xml.

  g_add_db_max_lines = 500.

  REFRESH:
  gt_tadir.

  IF p_pack IS INITIAL AND p_db IS INITIAL.
    WRITE: / text-005.
  ELSEIF p_folder IS INITIAL.
    WRITE: / text-006.
  ELSEIF p_csv IS INITIAL AND p_xml IS INITIAL.
    WRITE: / text-014.
  ELSE.
*DB-Tables
    IF NOT p_pack IS INITIAL
    AND NOT p_db IS INITIAL.
      SELECT * FROM tadir
          INTO TABLE lt_tadir
          WHERE pgmid = 'R3TR'
          AND object = 'TABL'
          AND obj_name IN p_db
          AND devclass IN p_pack.
    ELSEIF NOT p_pack IS INITIAL.
      SELECT * FROM tadir
          INTO TABLE lt_tadir
          WHERE pgmid = 'R3TR'
          AND object = 'TABL'
          AND devclass IN p_pack.
    ELSEIF NOT p_db IS INITIAL.
      SELECT * FROM tadir
          INTO TABLE lt_tadir
          WHERE pgmid = 'R3TR'
          AND object = 'TABL'
          AND obj_name IN p_db.
    ENDIF.
    LOOP AT lt_tadir ASSIGNING <ls_tadir>.
      l_tabname = <ls_tadir>-obj_name.
      SELECT SINGLE tabname FROM dd02l INTO l_tabname
          WHERE tabname = l_tabname
          AND as4local = 'A'
          AND tabclass = 'TRANSP'.
      IF sy-subrc = 0.
        APPEND <ls_tadir> TO gt_tadir.
      ENDIF.
    ENDLOOP.
*Other Parameters
    g_folder = p_folder.
    g_add_db_format_csv = p_csv.
    g_add_db_format_xml = p_xml.
    g_add_db_max_lines = p_max.
  ENDIF.

END-OF-SELECTION.

  IF NOT gt_tadir IS INITIAL.
    PERFORM start_download.

    WRITE: 'Database tables have been downloaded successfully.'.
  ENDIF.


*-----------------------------------------------------------------------
* form: start_download
*-----------------------------------------------------------------------
FORM start_download.
  DATA:
  l_tabname TYPE tabname,
  lt_string TYPE it_string.

  FIELD-SYMBOLS:
  <ls_tadir> TYPE tadir.

  LOOP AT gt_tadir ASSIGNING <ls_tadir>.
    l_tabname = <ls_tadir>-obj_name.
    IF g_add_db_format_csv = abap_true.
      PERFORM data2csv
        USING l_tabname
        CHANGING lt_string.
      PERFORM download
        USING
          <ls_tadir>-devclass
          l_tabname
          gc_extension_csv
          lt_string.
    ENDIF.
    IF g_add_db_format_xml = abap_true.
      PERFORM data2xml
        USING l_tabname
        CHANGING lt_string.
      PERFORM download
        USING
          <ls_tadir>-devclass
          l_tabname
          gc_extension_xml
          lt_string.
    ENDIF.
  ENDLOOP.

ENDFORM.                    "start_download
*&---------------------------------------------------------------------*
*&  Include           ZUTIL_CONVERT_TEXT                               *
*&                                                                     *
*&---------------------------------------------------------------------*
*&                                                                     *
*& This file is part of ZUTIL.                                         *
*&                                                                     *
*& ZUTIL is free software: you can redistribute it and/or modify       *
*& it under the terms of the GNU General Public License as published   *
*& by the Free Software Foundation, either version 3 of the License,   *
*& or any later version.                                               *
*&                                                                     *
*& ZUTIL is distributed in the hope that it will be useful,            *
*& but WITHOUT ANY WARRANTY; without even the implied warranty of      *
*& MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
*& GNU General Public License for more details.                        *
*&                                                                     *
*& You should have received a copy of the GNU General Public License   *
*& along with ZUTIL. If not, see <http://www.gnu.org/licenses/>.       *
*&                                                                     *
*&---------------------------------------------------------------------*
*&                                                                     *
*&  Author:     Ruediger von Creytz     ruediger.creytz@globalbit.net  *
*&  Copyright:  globalBIT, LLC          http://www.globalbit.net       *
*&                                                                     *
*&---------------------------------------------------------------------*


*-----------------------------------------------------------------------
* decode_html
*-----------------------------------------------------------------------
FORM decode_html
  CHANGING
    c_txt TYPE any.

  DATA:
  l_xstr TYPE xstring,
  l_hex TYPE string,
  l_xpos TYPE i,
  l_str TYPE string,
  l_fdpos TYPE i,
  l_strlen TYPE i,
  l_out TYPE string,
  l_outlen TYPE i,
  l_char TYPE string.

  CHECK NOT c_txt IS INITIAL.
  CHECK c_txt CS '&#x'.

  l_str = c_txt.

  DO.
    IF l_str CS '&#x'.
      l_fdpos = sy-fdpos.
      IF l_fdpos > 0.
        CONCATENATE l_out+0(l_outlen) l_str+0(l_fdpos) INTO l_out.
        l_outlen = l_outlen + l_fdpos.
      ENDIF.
      l_xpos = l_fdpos + 3.
      l_strlen = strlen( l_str ).
      l_strlen = l_strlen - l_xpos.
      l_str = l_str+l_xpos(l_strlen).
      SPLIT l_str AT ';' INTO l_hex l_str.
      l_xstr = l_hex.

      CALL FUNCTION 'NLS_STRING_CONVERT_TO_SYS'
        EXPORTING
          lang_used = sy-langu
          SOURCE    = l_xstr
        IMPORTING
          RESULT    = l_char
        EXCEPTIONS
          OTHERS    = 1.
      IF sy-subrc = 0.
        CONCATENATE l_out+0(l_outlen) l_char+0(1) INTO l_out.
      ELSE.
        CONCATENATE l_out+0(l_outlen) '#' INTO l_out.
      ENDIF.
      l_outlen = l_outlen + 1.
    ELSE.
      EXIT.
    ENDIF.
  ENDDO.

  l_strlen = strlen( l_str ).
  CONCATENATE l_out+0(l_outlen) l_str+0(l_strlen) INTO l_out.
  c_txt = l_out.
ENDFORM.                    "decode_html


*-----------------------------------------------------------------------
* decode_html_io
*-----------------------------------------------------------------------
FORM decode_html_io
  USING
    i_html TYPE string
  CHANGING
    c_txt TYPE any.

  c_txt = i_html.

  PERFORM decode_html
    CHANGING
      c_txt.

ENDFORM.                    "decode_html_io


*-----------------------------------------------------------------------
* encode_html
*-----------------------------------------------------------------------
FORM encode_html
  CHANGING
    c_txt TYPE string.

  CHECK NOT c_txt IS INITIAL.
  CHECK c_txt NS '&#'.

  PERFORM encode_html_force
    CHANGING c_txt.

ENDFORM.                    "encode_html


*-----------------------------------------------------------------------
* encode_html_force
*-----------------------------------------------------------------------
FORM encode_html_force
  CHANGING
    c_txt TYPE string.

  DATA:
  l_xstr TYPE xstring,
  l_hex TYPE string,
  l_hexlen TYPE i,
  l_xlen TYPE i,
  l_xpos TYPE i,
  l_str TYPE string,
  l_strlen TYPE i,
  l_out TYPE string,
  l_outlen TYPE i,
  l_pos TYPE i,
  l_chars(255) TYPE c,
  l_xchar(4) TYPE c.


  CHECK NOT c_txt IS INITIAL.

  CONCATENATE         "characters not to encode
    ' :;,./()-_+*#='
    '0123456789'
    'abcdefghijklmnopqrstuvwxyz'
    'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
    INTO l_chars.

  l_str = c_txt.


  CALL FUNCTION 'NLS_STRING_CONVERT_FROM_SYS'
    EXPORTING
      lang_used = sy-langu
      SOURCE    = l_str
    IMPORTING
      RESULT    = l_xstr.

  l_hex = l_xstr.
  l_hexlen = strlen( l_hex ).
  l_strlen = strlen( l_str ).
  l_xlen = l_hexlen / l_strlen.

  DO.
    l_xpos = l_pos * l_xlen.
    l_xchar = l_hex+l_xpos(l_xlen).
    IF l_chars NA l_str+l_pos(1)
    AND NOT l_xchar = '23'.
      IF l_outlen = 0.
        CONCATENATE '&#x' l_xchar ';' INTO l_out.
      ELSE.
        CONCATENATE l_out+0(l_outlen) '&#x' l_xchar ';'
          INTO l_out.
      ENDIF.
      l_outlen = l_outlen + 4 + l_xlen.
    ELSE.
      IF l_outlen = 0.
        l_out = l_str+l_pos(1).
      ELSE.
        CONCATENATE l_out+0(l_outlen) l_str+l_pos(1) INTO l_out.
      ENDIF.
      l_outlen = l_outlen + 1.
    ENDIF.

    l_pos = l_pos + 1.
    l_strlen = strlen( l_str ).
    IF l_pos = l_strlen.
      EXIT.
    ENDIF.
  ENDDO.

  c_txt = l_out.
ENDFORM.                    "encode_html_force


*-----------------------------------------------------------------------
* form: encode_uri
*-----------------------------------------------------------------------
FORM encode_uri
  CHANGING
    c_url TYPE string.

  DATA:
  l_prot TYPE string,
  l_url TYPE string,
  l_params TYPE string,
  lt_param TYPE it_string,
  l_key TYPE string,
  l_value TYPE string,
  l_len TYPE i.

  FIELD-SYMBOLS:
  <l_param> TYPE string.

  CHECK NOT c_url IS INITIAL.

  IF c_url CA '?' OR c_url NA '='.
    SPLIT c_url AT '?' INTO l_url l_params.
    IF l_url CA ':'.
      SPLIT l_url AT ':' INTO l_prot l_url.
    ENDIF.
    PERFORM encode_uri_link CHANGING l_url.
    IF NOT l_prot IS INITIAL.
      CONCATENATE l_prot ':' l_url INTO l_url.
    ENDIF.
    CONCATENATE l_url '?' INTO l_url.
  ELSEIF c_url CA '='.
    l_params = c_url.
  ENDIF.

  SPLIT l_params AT '&' INTO TABLE lt_param.
  LOOP AT lt_param ASSIGNING <l_param>.
    CLEAR: l_key, l_value.
    SPLIT <l_param> AT '=' INTO l_key l_value.
    PERFORM encode_uri_value CHANGING l_value.
    CONCATENATE l_url l_key '=' l_value '&' INTO l_url.
  ENDLOOP.

  l_len = strlen( l_url ).
  l_len = l_len - 1. "remove last '&'
  c_url = l_url+0(l_len).
ENDFORM.                    "encode_uri


*-----------------------------------------------------------------------
* form: encode_uri_link
*-----------------------------------------------------------------------
FORM encode_uri_link
  CHANGING
    c_value TYPE string.

  DATA:
  l_chars(66) TYPE c.

  CHECK NOT c_value IS INITIAL.

  CONCATENATE         "characters not to encode
    '/_-.'
    '0123456789'
    'abcdefghijklmnopqrstuvwxyz'
    'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
    INTO l_chars.

  PERFORM encode_uri_string
    USING l_chars
    CHANGING c_value.

ENDFORM.                    "encode_uri_link


*-----------------------------------------------------------------------
* form: encode_uri_string
*-----------------------------------------------------------------------
FORM encode_uri_string
  USING
    value(i_chars)
  CHANGING
    c_value TYPE string.

  DATA:
  l_xstr TYPE xstring,
  l_hex TYPE string,
  l_hexlen TYPE i,
  l_chex TYPE string,
  l_chex_pos TYPE i,
  l_xlen TYPE i,
  l_xpos TYPE i,
  l_str TYPE string,
  l_strlen TYPE i,
  l_out TYPE string,
  l_outlen TYPE i,
  l_pos TYPE i.

  CHECK NOT c_value IS INITIAL.

  l_str = c_value.


  CALL FUNCTION 'NLS_STRING_CONVERT_FROM_SYS'
    EXPORTING
      lang_used = sy-langu
      SOURCE    = l_str
    IMPORTING
      RESULT    = l_xstr.

  l_hex = l_xstr.
  l_hexlen = strlen( l_hex ).
  l_strlen = strlen( l_str ).
  l_xlen = l_hexlen / l_strlen.

  DO.
    IF i_chars NA l_str+l_pos(1).
      l_xpos = l_pos * l_xlen.
      l_chex = l_hex+l_xpos(l_xlen).
      l_chex_pos = strlen( l_chex ).
      l_chex_pos = l_chex_pos - 2.
      l_chex = l_chex+l_chex_pos(2).
      IF l_outlen = 0.
        CONCATENATE '%' l_chex INTO l_out.
      ELSE.
        CONCATENATE l_out+0(l_outlen) '%' l_chex
          INTO l_out.
      ENDIF.
      l_outlen = l_outlen + 3.
    ELSE.
      IF l_outlen = 0.
        l_out = l_str+l_pos(1).
      ELSE.
        CONCATENATE l_out+0(l_outlen) l_str+l_pos(1) INTO l_out.
      ENDIF.
      l_outlen = l_outlen + 1.
    ENDIF.

    l_pos = l_pos + 1.
    l_strlen = strlen( l_str ).
    IF l_pos = l_strlen.
      EXIT.
    ENDIF.
  ENDDO.

  c_value = l_out.
ENDFORM.                    "encode_uri_string


*-----------------------------------------------------------------------
* form: encode_uri_value
*-----------------------------------------------------------------------
FORM encode_uri_value
  CHANGING
    c_value TYPE string.

  DATA:
  l_chars(62) TYPE c.

  CHECK NOT c_value IS INITIAL.

  CONCATENATE         "characters not to encode
    '0123456789'
    'abcdefghijklmnopqrstuvwxyz'
    'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
    INTO l_chars.

  PERFORM encode_uri_string
    USING l_chars
    CHANGING c_value.

ENDFORM.                    "encode_uri_value
*&---------------------------------------------------------------------*
*&  Include           ZUTIL_CMD_REPLACE_OLD                            *
*&                                                                     *
*&---------------------------------------------------------------------*
*&                                                                     *
*& This file is part of ZUTIL.                                         *
*&                                                                     *
*& ZUTIL is free software: you can redistribute it and/or modify       *
*& it under the terms of the GNU General Public License as published   *
*& by the Free Software Foundation, either version 3 of the License,   *
*& or any later version.                                               *
*&                                                                     *
*& ZUTIL is distributed in the hope that it will be useful,            *
*& but WITHOUT ANY WARRANTY; without even the implied warranty of      *
*& MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
*& GNU General Public License for more details.                        *
*&                                                                     *
*& You should have received a copy of the GNU General Public License   *
*& along with ZUTIL. If not, see <http://www.gnu.org/licenses/>.       *
*&                                                                     *
*&---------------------------------------------------------------------*
*&                                                                     *
*&  Author:     Ruediger von Creytz     ruediger.creytz@globalbit.net  *
*&  Copyright:  globalBIT, LLC          http://www.globalbit.net       *
*&                                                                     *
*&---------------------------------------------------------------------*


*-----------------------------------------------------------------------
* replace_all
*-----------------------------------------------------------------------
FORM replace_all
  USING
    value(i_old)
    value(i_new)
  CHANGING
    c_str TYPE any.

  DO.
    IF c_str NS i_old.
      EXIT.
    ENDIF.
    PERFORM replace_single
      USING i_old i_new
      CHANGING c_str.
  ENDDO.

ENDFORM.                    "replace_all


*-----------------------------------------------------------------------
* replace_single
*-----------------------------------------------------------------------
FORM replace_single
  USING
    value(i_old)
    value(i_new)
  CHANGING
    c_str TYPE any.

  REPLACE i_old WITH i_new INTO c_str.

ENDFORM.                    "replace_single