⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 encryption.txt

📁 使用sap abap4 编写的 编码/解码程序。
💻 TXT
📖 第 1 页 / 共 3 页
字号:

**************************************************
* Encrypted & decrypted data is held here
TYPES: BEGIN OF t_bfzip_str,
        line(1024) TYPE x,
       END OF t_bfzip_str.
* Encrypted & decrypted data is held here
TYPES: BEGIN OF t_bfzipc_str,
        line(1024) TYPE c,
       END OF t_bfzipc_str.

TYPES: t_bfzip_tab TYPE TABLE OF t_bfzip_str.
TYPES: t_bfzipc_tab TYPE TABLE OF t_bfzipc_str.


TYPES: t_passwd(72) TYPE c.
TYPES: t_xpasswd(72) TYPE x.
*---------------------------------------------------------------------*
*       CLASS cl_zbfz DEFINITION
*---------------------------------------------------------------------*
* BlowFish class definition                                     *
*---------------------------------------------------------------------*
CLASS cl_zbfz DEFINITION.
  PUBLIC SECTION.
    METHODS:
**************************************************
* encryption
      encrypt
        IMPORTING it_flat_x TYPE t_bfzip_tab OPTIONAL
                  it_flat_c TYPE t_bfzipc_tab OPTIONAL
                  iv_size_flat TYPE i
        EXPORTING ev_size TYPE i
        CHANGING ct_encrypted TYPE t_bfzip_tab
                 EXCEPTIONS table_empty
                    table_too_small,

**************************************************
* decryption
      decrypt
        IMPORTING it_encrypted TYPE t_bfzip_tab
                  iv_size TYPE i
        EXPORTING ev_size TYPE i
        CHANGING  ct_flat_x TYPE t_bfzip_tab OPTIONAL
                  ct_flat_c TYPE t_bfzipc_tab OPTIONAL
        EXCEPTIONS wrong_password
                 table_empty
                    table_too_small,

**************************************************
* set new password (key generating)
      setpasswd
        IMPORTING iv_passwd TYPE t_passwd."TYPE string. "t_passwd.

  PRIVATE SECTION.

**************************************************
* Types
    TYPES: t_word_base(4) TYPE x.
    TYPES: t_fword3(16) TYPE x.
    TYPES: t_wordt TYPE STANDARD TABLE OF t_word_base.

**************************************************
* methods for internal use
    METHODS:
**************************************************
* check input table
     check_table
       IMPORTING it_data TYPE t_bfzip_tab
                 iv_size TYPE i
       EXCEPTIONS table_empty
                  table_too_small,

**************************************************
* internal arrays initialization
      reset,
**************************************************
* generate keys for current password
     generatesubkeys
       IMPORTING iv_passwd TYPE t_xpasswd
                 iv_length TYPE i,

**************************************************
* one word encryption
     bf_encoding
       CHANGING cv_w1 TYPE t_word_base
                 cv_w2 TYPE t_word_base,
**************************************************
* one word decription
     bf_decoding
       CHANGING cv_w1 TYPE t_word_base
                 cv_w2 TYPE t_word_base,
**************************************************
* word transformation
    fw
       IMPORTING iv_w TYPE t_word_base
       EXPORTING ev_w TYPE t_word_base,

**************************************************
* convert table to xstring
     convert_tab2xstr
       IMPORTING it_in TYPE t_bfzip_tab
                 iv_size TYPE i
       EXPORTING ev_out TYPE xstring,
**************************************************
* convert xstring to table
     convert_xstr2tab
       IMPORTING iv_in TYPE xstring
       EXPORTING et_out TYPE t_bfzip_tab
                 ev_size TYPE i,
**************************************************
* calculate check sum
     calc_check_sum
       IMPORTING it_flat TYPE t_bfzip_tab
                 iv_size TYPE i
       EXPORTING ev_checksum TYPE t_word_base
       .
**************************************************
* DATA section

**************************************************
* subkeys (72 bytes)
    DATA: pa TYPE t_wordt.

**************************************************
* key (256 lines of 4x4 byte words)
    DATA: sb TYPE TABLE OF t_fword3.
ENDCLASS.                    "cl_zbfz DEFINITION

*---------------------------------------------------------------------*
*       CLASS cl_zbfz IMPLEMENTATION
*---------------------------------------------------------------------*
* BlowFish and ZIP class implementation                               *
*---------------------------------------------------------------------*
CLASS cl_zbfz IMPLEMENTATION.
**************************************************
* checki nput table
  METHOD check_table.
    DATA: lv_lines TYPE i.
    IF iv_size < 8.
      RAISE table_too_small.
    ENDIF.
    DESCRIBE TABLE it_data LINES lv_lines.
    IF lv_lines EQ 0.
      RAISE table_empty.
    ENDIF.

  ENDMETHOD.                    "check_table
*       importing it_data type t_bfzip_tab
*                 iv_size type i
*       exceptions table_empty
*                  table_too_small,
**************************************************
* calculate check sum
  METHOD calc_check_sum.
    FIELD-SYMBOLS: <fs_line> TYPE t_bfzip_str.
    DATA: lv_i TYPE i,
          lv_j TYPE i,
          lv_offset_start TYPE i,
          lv_offset TYPE i,
          lv_cur_len TYPE i.

    ev_checksum = 0.
    lv_j = 1.
    LOOP AT it_flat ASSIGNING <fs_line>.
      lv_cur_len = lv_j * 1024.
      IF iv_size < lv_cur_len.
        lv_cur_len = iv_size - ( lv_j  - 1 ) * 1024.
      ELSE.
        lv_cur_len = 1024.
      ENDIF.
      lv_i = 0.
*      lv_offset_start = ( lv_j - 1 ) * 1024.
      WHILE lv_i < lv_cur_len.
*        lv_offset = lv_offset_start + lv_i.
        ev_checksum = ev_checksum BIT-XOR <fs_line>-line+lv_i(4).
        lv_i = lv_i + 4.
      ENDWHILE.
      lv_j = lv_j + 1.
    ENDLOOP.
  ENDMETHOD.                    "calc_check_sum
*************************************************
* convert table to xstring
  METHOD convert_tab2xstr.
*    DATA: lv_cur_size TYPE i.
*    DATA: lv_size TYPE i.
*    FIELD-SYMBOLS: <fs_tab> TYPE t_bfzip_str.
*
*    lv_size = 0.
*    lv_cur_size = 1024.
*    LOOP AT it_in ASSIGNING <fs_tab>.
*      IF lv_cur_size < iv_size.
*        CONCATENATE ev_out <fs_tab>-line INTO ev_out.
*      ELSE.
*        CONCATENATE ev_out <fs_tab>-line INTO ev_out.
*      ENDIF.
*      lv_size = lv_size + 1024.
*      lv_cur_size = lv_cur_size + 1024.
*
*    ENDLOOP.

    CALL FUNCTION 'SCMS_BINARY_TO_XSTRING'
      EXPORTING
        input_length       = iv_size
*   FIRST_LINE         = 0
*   LAST_LINE          = 0
     IMPORTING
       buffer             = ev_out
      TABLES
        binary_tab         = it_in
* EXCEPTIONS
*   FAILED             = 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.

  ENDMETHOD.                    "convert_tab2xstr
*************************************************
* convert xstring to table
  METHOD convert_xstr2tab.
    CALL FUNCTION 'SCMS_XSTRING_TO_BINARY'
      EXPORTING
        buffer                = iv_in
*        APPEND_TO_TABLE       = ' '
     IMPORTING
       output_length         = ev_size
      TABLES
        binary_tab            = et_out
              .
  ENDMETHOD.                    "convert_xstr2tab
**************************************************
* encryption
  METHOD encrypt.
    DATA: lv_ind TYPE i, lv_rest TYPE i.
    DATA: lv_offset TYPE i.
    DATA: lv_w1 TYPE t_word_base, lv_w2 TYPE t_word_base.
    DATA: lv_checksum TYPE t_word_base.
    DATA: lv_temp_size TYPE i.
    DATA: lv_lines TYPE i.
    DATA: lv_max TYPE i.
    DATA: lv_index TYPE i.
    DATA: ls_encrypted TYPE t_bfzip_str.
    DATA: lv_size TYPE i.
    DATA: it_flat TYPE t_bfzip_tab.
    DATA: iv_size TYPE i.

*   Firstly check that at least one of it_flat_x or it_flat_c parameters
*   are not empty
    IF it_flat_x IS INITIAL AND it_flat_c IS INITIAL.
      RAISE table_empty.
    ENDIF.


*   Firstly check whether it_flax_x is initial
    IF it_flat_x IS INITIAL.
*     Transform input data from c to x type
      CALL FUNCTION 'SCMS_FTEXT_TO_BINARY'
      EXPORTING
        input_length          = iv_size_flat
*       FIRST_LINE            = 0
*       LAST_LINE             = 0
*       APPEND_TO_TABLE       = ' '
*       MIMETYPE              = ' '
      IMPORTING
        OUTPUT_LENGTH         = iv_size
      TABLES
        ftext_tab             = it_flat_c
        binary_tab            = it_flat.
*     EXCEPTIONS
*       FAILED                = 1
*       OTHERS                = 2
    ELSE.
*     if it is not, copy it_flat_x data to it_flat
      it_flat = it_flat_x.
      iv_size = iv_size_flat.
    ENDIF.


    FIELD-SYMBOLS: <fs_wa> TYPE t_bfzip_str.

    CALL METHOD check_table
      EXPORTING
        it_data         = it_flat
        iv_size         = iv_size
      EXCEPTIONS
        table_empty     = 1
        table_too_small = 2.

    CASE sy-subrc.
      WHEN 1. RAISE table_empty.
      WHEN 2. RAISE table_too_small.
    ENDCASE.


    CLEAR ct_encrypted[].

* we need this for case if import & export size have the same reference
    lv_size = iv_size.

    CALL METHOD calc_check_sum
      EXPORTING
        it_flat     = it_flat
        iv_size     = lv_size
      IMPORTING
        ev_checksum = lv_checksum.


    lv_rest = iv_size MOD 8.

    IF lv_rest NE 0.
      lv_rest = 8 - lv_rest.
    ELSE.
      lv_rest = 0.
    ENDIF.

    lv_temp_size = lv_size + lv_rest.
    ev_size = lv_temp_size + 8.
    DESCRIBE TABLE it_flat LINES lv_lines.

    lv_max = 1024.
    lv_index = 1.
    LOOP AT it_flat ASSIGNING <fs_wa>.
      lv_ind = 0.
      IF lv_index = lv_lines.
        lv_max = lv_temp_size - 1024 * ( lv_lines - 1 ).
      ENDIF.
      WHILE lv_ind < lv_max.
        lv_offset = lv_ind + 4.
        lv_w1 = <fs_wa>-line+lv_ind(4).
        lv_w2 = <fs_wa>-line+lv_offset(4).
        CALL METHOD bf_encoding
          CHANGING
            cv_w1 = lv_w1
            cv_w2 = lv_w2.
        ls_encrypted-line+lv_ind(4) = lv_w1.
        ls_encrypted-line+lv_offset(4) = lv_w2.
        lv_ind = lv_ind + 8.
      ENDWHILE.

      IF lv_index = lv_lines.
        IF lv_max NE 1024.
          lv_w1 = lv_checksum.
          lv_w2 = lv_size.
          CALL METHOD bf_encoding
            CHANGING
              cv_w1 = lv_w1
              cv_w2 = lv_w2.
          ls_encrypted-line+lv_max(4) = lv_w1.
          lv_max = lv_max + 4.
          ls_encrypted-line+lv_max(4) = lv_w2.
        ELSE.
          APPEND ls_encrypted TO ct_encrypted.
          CLEAR ls_encrypted.
          lv_w1 = lv_checksum.
          lv_w2 = lv_size.
          CALL METHOD bf_encoding
            CHANGING
              cv_w1 = lv_w1
              cv_w2 = lv_w2.
          ls_encrypted-line+lv_max(4) = lv_w1.
          lv_max = lv_max + 4.
          ls_encrypted-line+lv_max(4) = lv_w2.
        ENDIF.
      ENDIF.
      APPEND ls_encrypted TO ct_encrypted.
      lv_index = lv_index + 1.
    ENDLOOP.

    CALL METHOD reset.

  ENDMETHOD.                    "encrypt

*****************************************************
* Decryption

  METHOD decrypt.
    DATA: lv_ind TYPE i.
    DATA: lv_offset TYPE i.
    DATA: lv_w1 TYPE t_word_base, lv_w2 TYPE t_word_base.
    DATA: lv_lines TYPE i.
    DATA: len TYPE i.

    FIELD-SYMBOLS: <fs_wa> TYPE t_bfzip_str.
    DATA: ls_flat TYPE t_bfzip_str.

    CLEAR ct_flat_x[].
    CLEAR ct_flat_c[].




    LOOP AT it_encrypted ASSIGNING <fs_wa>.
      lv_ind = 0.
      WHILE lv_ind < 1024.
        lv_offset = lv_ind + 4.
        lv_w1 = <fs_wa>-line+lv_ind(4).
        lv_w2 = <fs_wa>-line+lv_offset(4).
        CALL METHOD bf_decoding
          CHANGING
            cv_w1 = lv_w1
            cv_w2 = lv_w2.
        ls_flat-line+lv_ind(4) = lv_w1.
        ls_flat-line+lv_offset(4) = lv_w2.
        lv_ind = lv_ind + 8.
      ENDWHILE.
      APPEND ls_flat TO ct_flat_x.
    ENDLOOP.

    DESCRIBE TABLE ct_flat_x LINES lv_lines.
    lv_ind = iv_size - ( lv_lines - 1 ) * 1024 - 8.
    IF lv_ind = 0.
      DELETE ct_flat_x INDEX lv_lines.
    ENDIF.
    lv_w1 = ls_flat-line+lv_ind(4).
    lv_ind = lv_ind + 4.
    ev_size = ls_flat-line+lv_ind(4).


    CALL METHOD calc_check_sum
      EXPORTING
        it_flat     = ct_flat_x
        iv_size     = ev_size
      IMPORTING

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -