Application Development Discussions
Join the discussions or start your own on all things application development, including tools and APIs, programming models, and keeping your skills sharp.
cancel
Showing results for 
Search instead for 
Did you mean: 

SO_NEW_DOCUMENT_SEND_API1

Former Member
0 Kudos

hi,

is it possible to send an attachment with help of this function module and at the same time give some message in the body.

if so, please give an example.

helpful answers will be rewarded.

4 REPLIES 4

Former Member
0 Kudos

Hi,

Here is the code to send message with the attachment... just go through this . i hope will give u some help..

program zemailtest_with_attachment.

  • This example shows how to send

  • - a simple text provided in an internal table of text lines

  • - and an attached MS word document provided in internal table

  • - to some internet email address.

*

class ca_sapuser_bcs definition load.

class cl_cam_address_bcs definition load.

data: send_request type ref to cl_bcs.

data: text type bcsy_text.

data: binary_content type solix_tab.

data: document type ref to cl_document_bcs.

data: sender type ref to cl_sapuser_bcs.

data: recipient type ref to if_recipient_bcs.

data: bcs_exception type ref to cx_bcs.

data: sent_to_all type os_boolean.

data: document_data like sofolenti1,

doc_id like sofolenti1-doc_id,

cont_hex like solix occurs 100,

cont_text type soli_tab,

cont_hex1 like solix occurs 10.

data: attachment type ref to if_document_bcs.

start-of-selection.

perform main.

----


  • FORM main *

----


form main.

try.

  • -------- create persistent send request ------------------------

send_request = cl_bcs=>create_persistent( ).

  • -------- create and set document with attachment ---------------

  • create document from internal table with text

append 'Hello world!' to text.

document = cl_document_bcs=>create_document(

i_type = 'RAW'

i_text = text

i_length = '12'

i_subject = 'main document created by whatever ' ).

  • create attachment

clear text.

append 'This is the attachment text!' to text. "#EC NOTEXT

attachment = cl_document_bcs=>create_document(

i_type = 'RAW'

i_text = text

i_length = '11'

i_subject = 'attachment...' ).

  • add (existing) attachment to main document

call method document->add_document_as_attachment

exporting

im_document = attachment

.

  • add document to send request

call method send_request->set_document( document ).

  • --------- add recipient (e-mail address) -----------------------

  • create recipient

recipient = cl_cam_address_bcs=>create_internet_address( " your email address

'youremailaddres here ' ).

  • add recipient with its respective attributes to send request

call method send_request->add_recipient

exporting

i_recipient = recipient

i_express = 'X'.

  • ---------- send document ---------------------------------------

send_request->send_request->set_link_to_outbox( 'X' ).

call method send_request->send(

exporting

i_with_error_screen = 'X'

receiving

result = sent_to_all ).

if sent_to_all = 'X'.

write text-003.

endif.

commit work.

  • -----------------------------------------------------------

  • * exception handling

  • -----------------------------------------------------------

  • * replace this very rudimentary exception handling

  • * with your own one !!!

  • -----------------------------------------------------------

catch cx_bcs into bcs_exception.

write: 'error resultes.'(001).

write: 'messtype:'(002), bcs_exception->error_type.

exit.

endtry.

endform.

Thanks & Regards

Ashu Singh

Former Member
0 Kudos

hiii

yse we can send an attachment by using this FM and can write some message too..just refer to following code

SET BODY-TEXT (if any)...
* IF NOT t_content[] IS INITIAL.
  IF NOT t_con_text[] IS INITIAL.
*   t_con_text[] = t_content[].

*   Write Packing List (Main) for BODY-TEXT
    DESCRIBE TABLE t_con_text LINES h_tab_cntr.
    READ TABLE t_con_text INDEX h_tab_cntr.
    h_doc_data-doc_size = ( h_tab_cntr - 1 )
                        * 255 + STRLEN( t_con_text ).
    CLEAR t_pak_list.
    t_pak_list-head_start = 1.
    t_pak_list-head_num = 0.
    t_pak_list-body_start = 1.
    t_pak_list-body_num = h_tab_cntr.
    t_pak_list-doc_type = 'RAW'.
    APPEND t_pak_list.
  ELSE.
*   Write Packing List (Main) for NO BODY-TEXT (force spaces)
    t_con_text = space. APPEND t_con_text.
    CLEAR t_pak_list.
    t_pak_list-head_start = 1.
    t_pak_list-head_num = 0.
    t_pak_list-body_start = 1.
    t_pak_list-body_num = 1.
    t_pak_list-doc_type = 'RAW'.
    APPEND t_pak_list.
  ENDIF.
*   ofttab-tdprintcom = 'EP'.
* Check for OTF-2-PDF attachment (via T_ITCOO input table)...
  IF NOT ofttab[] IS INITIAL.           " Something passed?
    h_commit_wk = space.               " YES - reset commit-work
    t_itcoo[] = ofttab[].               " ... - set OTF file...
    PERFORM convert_otf_2_pdf.         " ... - go convert to PDF...

    perform conversion_of_size.

  ENDIF.

* Check for NO OTF-2-PDF attachment & Spool-ID...
  IF ofttab[] IS INITIAL AND            " Empty &
     NOT d_spool_id IS INITIAL.        " .. got SPOOL number?
*    SELECT SINGLE rqident              " YES - check for valid
*             INTO tsp01-rqident        " ... - .. entry in
*             FROM tsp01                " ... - ... spool...
*            WHERE rqident = d_spool_id.                     "
    IF sy-subrc NE 0.                  " ... - Nothing?
      RAISE invalid_spool_id.          " ... - YES - post it...
    ELSE.                              " ... - NO  -
      PERFORM convert_otf_2_pdf_sx.    " ... - convert to PDF (new way)!
     perform conversion_of_size.

    ENDIF.
  ENDIF.

* Begin of ADDS for project ENABLE
* Check for ABAPLIST as attachment (via T_ABABLIST input table)...
*  IF NOT t_abaplist[] IS INITIAL.      " Something passed?
*    t_list[] = t_abaplist[].           " YES - set table...
*    IF d_desired_type IS INITIAL.      " ... - desired type passed?
*      d_desired_type = 'RAW'.          " ... - NO  - set default
*    ENDIF.                             " ... - end...
*  ENDIF.                               " end...

  FIELD-SYMBOLS:
    <fs_org> TYPE ANY,
    <fs_kunnr> TYPE ANY.
  DATA:
    w_salorg_field(20) TYPE c,
    w_kunnr_field(20) TYPE c,
    w_subrc.

  DATA:
    w_departure_ctry LIKE adrc-country,
    w_destination_ctry LIKE adrc-country.

    IF nast-kschl = 'ZDA0' OR
       nast-kschl = 'ZDAS' OR
       nast-kschl = 'ZPAS' OR
       nast-kschl = 'ZQCA'.
      MOVE:
        'VBDKL-VKORG' TO w_salorg_field,
        'VBDKL-KUNWE' TO w_kunnr_field.

    ELSEIF nast-kschl EQ 'ZBA0'.
      MOVE:
        'VBDKA-VKORG' TO w_salorg_field,
        'VBDKA-KUNNR' TO w_kunnr_field.

    ELSEIF nast-kschl EQ 'ZRD3'.
      MOVE:
        'VBDKR-VKORG' TO w_salorg_field,
        'VBDKR-KUNRE' TO w_kunnr_field.

    ELSEIF nast-kschl EQ 'ZLR0'.
      MOVE:
        'VBRK-VKORG' TO w_salorg_field,
        'W_BILLTO' TO w_kunnr_field.
    ENDIF.

    IF w_salorg_field IS NOT INITIAL.
      ASSIGN (w_salorg_field) TO <fs_org>.
* Select the Departure Country
      SELECT SINGLE country
        INTO w_departure_ctry
        FROM tvko AS t JOIN adrc AS a
          ON t~adrnr EQ a~addrnumber
       WHERE t~vkorg EQ <fs_org>
         AND a~date_from LE sy-datum.
    ENDIF.

    IF w_kunnr_field IS NOT INITIAL.
      ASSIGN (w_kunnr_field) TO <fs_kunnr>.
* select destination country
      SELECT SINGLE land1
        FROM kna1
        INTO w_destination_ctry
       WHERE kunnr EQ <fs_kunnr>.
    ENDIF.
* Compare the destination and departure country
* Send PDF to Application server only if destination and departure countries will be the same
* This is because ALE output will not be triggered for Export customers
*  if nast-nacha eq '5'.                "
    IF w_destination_ctry IS NOT INITIAL AND
       w_departure_ctry IS NOT INITIAL.
      IF w_destination_ctry EQ w_departure_ctry.
        MOVE 'X' TO w_subrc.

      ENDIF.
    ENDIF.
*  endif.                               " if nast-nacha ne '7'.
*    IF w_subrc EQ 'X'.
*
      IF nast-kschl = 'ZDA0' OR
         nast-kschl = 'ZDAS' OR
         nast-kschl = 'ZRD3' OR
         nast-kschl = 'ZBA0' OR
         nast-kschl = 'ZPAS' OR             " D47K915851
         nast-kschl = 'ZQCA' OR             " D47K915851
         nast-kschl = 'ZLR0'.               

*   Finding the Company Code
        CASE nast-kschl.

          WHEN 'ZDA0'.
            MOVE 'VBDKL-BUKRS' TO w_field.
            WRITE (w_field) TO w_ccode.
          WHEN  'ZDAS'.
            MOVE 'VBDKL-BUKRS' TO w_field.
            WRITE (w_field) TO w_ccode.
          WHEN 'ZRD3'.
            MOVE 'VBDKR-BUKRS' TO w_field.
            WRITE (w_field) TO w_ccode.
          WHEN 'ZBA0'.
            MOVE 'VBDKA-BUKRS_VF' TO w_field.
            WRITE (w_field) TO w_ccode.
          WHEN 'ZPAS'.
            MOVE 'VBDKL-BUKRS' TO w_field.
            WRITE (w_field) TO w_ccode.
          WHEN 'ZQCA'.
            MOVE 'VBDKL-BUKRS' TO w_field.
            WRITE (w_field) TO w_ccode.
          WHEN 'ZLR0'.                             
            MOVE 'VBRK-BUKRS' TO w_field.
            WRITE (w_field) TO w_ccode.

        ENDCASE.
        IF w_ccode EQ 'JP01'
         OR w_ccode EQ 'CN02'
         OR w_ccode EQ 'TW02'.


  IF t_soli[] IS NOT INITIAL.
    t_app_pdf[] = t_soli[].
*     Find the path of Logical System
    SELECT SINGLE outputdir
             FROM edipox
             INTO w_dsn
            WHERE port = w_port.
    CONCATENATE  w_dsn
                 nast-kschl '_'
                 nast-objky '_'
                 w_ccode
                 '.DAT'
            INTO w_dsn.

    CONDENSE w_dsn.
*   Storing the file in Appln. Server in above path
*    OPEN DATASET w_dsn FOR OUTPUT IN BINARY MODE.
*    IF sy-subrc = 0.
*      LOOP AT t_app_pdf.
*        TRANSFER t_app_pdf TO w_dsn.
*      ENDLOOP.
*      CLOSE DATASET w_dsn.
**    Nothing to do
*    ENDIF.                       " IF sy-subrc = 0.
  ENDIF.                         " IF t_soli[]
        ENDIF.                            " IF w_ccode eq 'JP01'
      ENDIF.                             " IF NAST-KSCHL
    ENDIF.
*  ENDIF.

** Check for any ATTACHMENTS...
 IF d_desired_type = 'RAW'.           " Set to RAW?
*    PERFORM convert_to_abaplist.       " YES - convert it
  ENDIF.                               " end...
  IF d_desired_type = 'ALI'.           " Set to ALI?
    PERFORM convert_to_alilist.        " YES - convert it
  ENDIF.                               " end...

* Check for any ATTACHMENTS...
  IF NOT t_soli[] IS INITIAL.          " attachment?
    h_real_type = d_desired_type.      " ENABLE
    h_transf_type = 'X'.               " Transfer type BINARY...


*   Write PDF/ALI formatted data to BINARY table...
    t_con_bin[] = t_soli[].

*   Add Packing List (attachment) for PDF...
    DESCRIBE TABLE t_con_bin LINES h_tab_cntr.
    READ TABLE t_con_bin INDEX h_tab_cntr.
    h_doc_data-doc_size = h_doc_data-doc_size
                        + ( ( h_tab_cntr - 1 )
                        * 255 + STRLEN( t_con_bin ) ).
    h_doc_data-obj_descr  = mail_subject.
    h_body_start = 1.
    h_body_num = h_tab_cntr.

*   Write RAW data if that's what it is (adds to TEXT)...
    IF h_real_type = 'RAW'.
      DESCRIBE TABLE t_con_text LINES h_body_start.
      h_body_start = h_body_start + 1.

      h_transf_type = space.           " Transfer type TEXT...
      LOOP AT t_con_bin.               " Zip thru TEXT stuff
        t_con_text = t_con_bin.        " set TEXT table header..
        APPEND t_con_text.             " add to what's there!
      ENDLOOP.
      CLEAR: t_con_bin.                " clear BINARY header..
      REFRESH: t_con_bin.              " reset BINARY table...
    ENDIF.

    CLEAR t_pak_list.
    IF h_transf_type = 'X'.            " Binary=PDF/ALI?
      t_pak_list-transf_bin = 'X'.
      t_pak_list-head_start = 1.
      t_pak_list-head_num   = 0.
      t_pak_list-body_start = 1.
      t_pak_list-body_num   = h_tab_cntr.
      t_pak_list-doc_type   = h_real_type.
      t_pak_list-obj_name   = 'ATTACHMENT'.
      t_pak_list-obj_descr  = 'Document'(001).
      t_pak_list-doc_size   = ( h_tab_cntr - 1 )
                            * 255 + STRLEN( t_con_bin ).
    ELSE.
      DESCRIBE TABLE t_con_text LINES h_tab_cntr.
      READ TABLE t_con_text INDEX h_tab_cntr.
      t_pak_list-transf_bin = ' '.     " Binary=RAW
      t_pak_list-head_start = 1.
      t_pak_list-head_num   = 0.
      t_pak_list-body_start = h_body_start.
      t_pak_list-body_num   = h_tab_cntr.
      t_pak_list-doc_type   = h_real_type.
      t_pak_list-obj_name   = 'ATTACHMENT'(002).
      t_pak_list-obj_descr  = 'Report'(003).
      t_pak_list-doc_size   = ( h_body_num - 1 )
                            * 255 + STRLEN( t_con_text ).
    ENDIF.
    APPEND t_pak_list.
  ENDIF.


* Send the EMAIL out with SAP function...
  CALL FUNCTION 'SO_NEW_DOCUMENT_ATT_SEND_API1'
    EXPORTING
      document_data              = h_doc_data
      put_in_outbox              = 'X'
*      commit_work                = 'X'
    TABLES
      packing_list               = t_pak_list
      contents_bin               = t_con_bin
      contents_txt               = t_con_text
      receivers                  = t_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.

  IF syst-subrc NE 0.
*    RAISE send_failed.
    CALL FUNCTION 'NAST_PROTOCOL_UPDATE'
      EXPORTING
        msg_arbgb = '00'
        msg_nr    = '001'
        msg_ty    = 'E'
        msg_v1    = 'O/P Could not be issued '(001)
        msg_v2    = ' Due to No Mail ID'(002)
        msg_v3    = syst-msgv3
        msg_v4    = syst-msgv4
      EXCEPTIONS
        OTHERS    = 1.
* Check General incompletion status of the header
    IF sy-subrc <> 0.
* MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
*         WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
    ELSE.
      WRITE : 'SENT'.
    ENDIF.

  ELSE.
*    commit work.
  ENDIF.

regards

twinkal

former_member181995
Active Contributor
0 Kudos

Answer is Definately Yes,

please read the documentation of SO_NEW_DOCUMENT_SEND_API1 in se37 you will get your answer by your self.

Amit.

Former Member
0 Kudos

Hi,

Yes it is possiable.

see this example code

report zcl_testmail.

tables: ekko.

parameters: p_email type somlreci1-receiver

default 'Ur mail address'.

types: begin of t_ekpo,

ebeln type ekpo-ebeln,

ebelp type ekpo-ebelp,

aedat type ekpo-aedat,

matnr type ekpo-matnr,

end of t_ekpo.

data: it_ekpo type standard table of t_ekpo initial size 0,

wa_ekpo type t_ekpo.

types: begin of t_charekpo,

ebeln(10) type c,

ebelp(5) type c,

aedat(8) type c,

matnr(18) type c,

end of t_charekpo.

data: wa_charekpo type t_charekpo.

data: it_message type standard table of solisti1 initial size 0

with header line.

data: it_attach type standard table of solisti1 initial size 0

with header line.

data: t_packing_list like sopcklsti1 occurs 0 with header line,

t_contents like solisti1 occurs 0 with header line,

t_receivers like somlreci1 occurs 0 with header line,

t_attachment like solisti1 occurs 0 with header line,

t_object_header like solisti1 occurs 0 with header line,

w_cnt type i,

w_sent_all(1) type c,

w_doc_data like sodocchgi1,

gd_error type sy-subrc,

gd_reciever type sy-subrc.

************************************************************************

*START_OF_SELECTION

start-of-selection.

  • Retrieve sample data from table ekpo

perform data_retrieval.

  • Populate table with detaisl to be entered into .xls file

perform build_xls_data_table.

************************************************************************

*END-OF-SELECTION

end-of-selection.

  • Populate message body text

perform populate_email_message_body.

  • Send file by email as .xls speadsheet

perform send_file_as_email_attachment

tables it_message

it_attach

using p_email

'Example .xls documnet attachment'

'XLS'

'filename'

' '

' '

' '

changing gd_error

gd_reciever.

  • Instructs mail send program for SAPCONNECT to send email(rsconn01)

perform initiate_mail_execute_program.

&----


*& Form DATA_RETRIEVAL

&----


  • Retrieve data form EKPO table and populate itab it_ekko

----


form data_retrieval.

select ebeln ebelp aedat matnr

up to 10 rows

from ekpo

into table it_ekpo.

endform. " DATA_RETRIEVAL

&----


*& Form BUILD_XLS_DATA_TABLE

&----


  • Build data table for .xls document

----


form build_xls_data_table.

constants: con_cret(20) type c value '0D', "OK for non Unicode

con_tab(20) type c value '09'. "OK for non Unicode

*If you have Unicode check active in program attributes thnen you will

*need to declare constants as follows

*class cl_abap_char_utilities definition load.

*constants:

  • con_tab type c value cl_abap_char_utilities=>HORIZONTAL_TAB,

  • con_cret type c value cl_abap_char_utilities=>CR_LF.

concatenate 'EBELN' 'EBELP' 'AEDAT' 'MATNR'

into it_attach separated by con_tab.

concatenate con_cret it_attach into it_attach.

append it_attach.

loop at it_ekpo into wa_charekpo.

concatenate wa_charekpo-ebeln wa_charekpo-ebelp

wa_charekpo-aedat wa_charekpo-matnr

into it_attach separated by con_tab.

concatenate con_cret it_attach into it_attach.

append it_attach.

endloop.

endform. " BUILD_XLS_DATA_TABLE

&----


*& Form SEND_FILE_AS_EMAIL_ATTACHMENT

&----


  • Send email

----


form send_file_as_email_attachment tables pit_message

pit_attach

using p_email

p_mtitle

p_format

p_filename

p_attdescription

p_sender_address

p_sender_addres_type

changing p_error

p_reciever.

data: ld_error type sy-subrc,

ld_reciever type sy-subrc,

ld_mtitle like sodocchgi1-obj_descr,

ld_email like somlreci1-receiver,

ld_format type so_obj_tp ,

ld_attdescription type so_obj_nam ,

ld_attfilename type so_obj_des ,

ld_sender_address like soextreci1-receiver,

ld_sender_address_type like soextreci1-adr_typ,

ld_receiver like sy-subrc.

ld_email = p_email.

ld_mtitle = p_mtitle.

ld_format = p_format.

ld_attdescription = p_attdescription.

ld_attfilename = p_filename.

ld_sender_address = p_sender_address.

ld_sender_address_type = p_sender_addres_type.

  • Fill the document data.

w_doc_data-doc_size = 1.

  • Populate the subject/generic message attributes

w_doc_data-obj_langu = sy-langu.

w_doc_data-obj_name = 'SAPRPT'.

w_doc_data-obj_descr = ld_mtitle .

w_doc_data-sensitivty = 'F'.

  • Fill the document data and get size of attachment

clear w_doc_data.

read table it_attach index w_cnt.

w_doc_data-doc_size =

( w_cnt - 1 ) * 255 + strlen( it_attach ).

w_doc_data-obj_langu = sy-langu.

w_doc_data-obj_name = 'SAPRPT'.

w_doc_data-obj_descr = ld_mtitle.

w_doc_data-sensitivty = 'F'.

clear t_attachment.

refresh t_attachment.

t_attachment[] = pit_attach[].

  • Describe the body of the message

clear t_packing_list.

refresh t_packing_list.

t_packing_list-transf_bin = space.

t_packing_list-head_start = 1.

t_packing_list-head_num = 0.

t_packing_list-body_start = 1.

describe table it_message lines t_packing_list-body_num.

t_packing_list-doc_type = 'RAW'.

append t_packing_list.

  • Create attachment notification

t_packing_list-transf_bin = 'X'.

t_packing_list-head_start = 1.

t_packing_list-head_num = 1.

t_packing_list-body_start = 1.

describe table t_attachment lines t_packing_list-body_num.

t_packing_list-doc_type = ld_format.

t_packing_list-obj_descr = ld_attdescription.

t_packing_list-obj_name = ld_attfilename.

t_packing_list-doc_size = t_packing_list-body_num * 255.

append t_packing_list.

  • Add the recipients email address

clear t_receivers.

refresh t_receivers.

t_receivers-receiver = ld_email.

t_receivers-rec_type = 'U'.

t_receivers-com_type = 'INT'.

t_receivers-notif_del = 'X'.

t_receivers-notif_ndel = 'X'.

append t_receivers.

call function 'SO_DOCUMENT_SEND_API1'

exporting

document_data = w_doc_data

put_in_outbox = 'X'

sender_address = ld_sender_address

sender_address_type = ld_sender_address_type

commit_work = 'X'

importing

sent_to_all = w_sent_all

tables

packing_list = t_packing_list

contents_bin = t_attachment

contents_txt = it_message

receivers = t_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.

  • Populate zerror return code

ld_error = sy-subrc.

  • Populate zreceiver return code

loop at t_receivers.

ld_receiver = t_receivers-retrn_code.

endloop.

endform.

&----


*& Form INITIATE_MAIL_EXECUTE_PROGRAM

&----


  • Instructs mail send program for SAPCONNECT to send email.

----


form initiate_mail_execute_program.

wait up to 2 seconds.

submit rsconn01 with mode = 'INT'

with output = 'X'

and return.

endform. " INITIATE_MAIL_EXECUTE_PROGRAM

&----


*& Form POPULATE_EMAIL_MESSAGE_BODY

&----


  • Populate message body text

----


form populate_email_message_body.

refresh it_message.

it_message = 'Hi this is a test mail'.

append it_message.

Endform.

You can check the mail in sost t-code.

hope it is helpful.