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: 

internal tabe to text file in application server

Former Member
0 Kudos

Hi Experts,

i want to downlaod internal table content into text file in applecation server .how it can be possible.

Thanks And Regards.

Priyank Dixit

1 ACCEPTED SOLUTION

Former Member
0 Kudos

hi,

try this sample code

tables: lfa1.

parameters: file(200) type c.

data: begin of itab occurs 0,

lifnr like lfa1-lifnr,

name1 like lfa1-name1,

ort01 like lfa1-ort01,

end of itab.

select lifnr name1 ort01 from lfa1 into table itab.

open dataset file for output in binary mode.

loop at itab .

transfer itab to file.

endloop.

close dataset file.

All the best

with regards

S.Janagar

it will work for sure

8 REPLIES 8

Former Member
0 Kudos

use OPEN DATASET and TRANSFER key words.

Former Member
0 Kudos

Hi,

Check this sample code


REPORT z_sdn.
DATA:
  BEGIN OF fs_flight,
    carrid   LIKE sflight-carrid,
    connid   LIKE sflight-connid,
    fldate   LIKE sflight-fldate,
    price    LIKE sflight-price,
    currency LIKE sflight-currency,
  END OF fs_flight.
DATA: fname TYPE string,
      w_flight TYPE string,
      w_line TYPE i,
      w_idx TYPE i VALUE 1,
      w_char VALUE '',
      wa_tab(72),
      w_price TYPE string.
DATA:
  t_flight LIKE
     TABLE OF
           fs_flight.

DATA:
  t_tab LIKE
     TABLE OF
           wa_tab.

SELECT-OPTIONS:
  s_carrid FOR fs_flight-carrid,
  s_connid FOR fs_flight-connid.

START-OF-SELECTION.
  PERFORM get_flight_data.
  fname = '.\flight.txt'.
  OPEN DATASET fname FOR OUTPUT IN BINARY MODE .
  DESCRIBE TABLE t_flight LINES w_line.
  DO w_line TIMES.
    READ TABLE t_flight INDEX w_idx INTO fs_flight.
    TRANSFER fs_flight TO fname .
    ADD 1 TO w_idx.
  ENDDO.
 CLOSE DATASET fname.
  IF sy-subrc EQ 0.
    WRITE: 'File Opened on Application server'.
  ELSE.
    WRITE: 'File could not be opened'.
  ENDIF.
*&---------------------------------------------------------------------
*
*&      Form  get_flight_data
*&---------------------------------------------------------------------
*
* This subroutine fetches the data from sflight table
*----------------------------------------------------------------------
*
*This subroutine does not have interface parameters
*----------------------------------------------------------------------

FORM get_flight_data .
  SELECT carrid
         connid
         fldate
         price
         currency
    FROM sflight
    INTO TABLE t_flight
   WHERE carrid IN s_carrid
     AND connid IN s_connid.

ENDFORM.                    " get_flight_data

Regards

Abhijeet

Former Member
0 Kudos

Hi,

Use Ws_download function Module,

Former Member
0 Kudos

hii,

hav u created internal table in report n want to take output in text file??

can u explain your problem

Thanks.

Former Member
0 Kudos

hi,

try this sample code

tables: lfa1.

parameters: file(200) type c.

data: begin of itab occurs 0,

lifnr like lfa1-lifnr,

name1 like lfa1-name1,

ort01 like lfa1-ort01,

end of itab.

select lifnr name1 ort01 from lfa1 into table itab.

open dataset file for output in binary mode.

loop at itab .

transfer itab to file.

endloop.

close dataset file.

All the best

with regards

S.Janagar

it will work for sure

Former Member
0 Kudos

hi priyak ,

you can use GUI DOWNLOAD function module for internal tabe to text file in application server

the sample code is here it will definately help you:

&----


*& Report Y1082CHD

*&

----


TABLES: vbak. " standard table

----


  • Type Pools *

----


TYPE-POOLS: slis.

*-- Structure to hold data from table CE1MCK2

TYPES: BEGIN OF tp_itab1,

vbeln LIKE vbap-vbeln,

posnr LIKE vbap-posnr,

werks LIKE vbap-werks,

lgort LIKE vbap-lgort,

END OF tp_itab1.

*-- Data Declaration

DATA: t_itab1 TYPE TABLE OF tp_itab1.

DATA : i_fieldcat TYPE slis_t_fieldcat_alv.

----


  • Selection Screen *

----


*--Sales document-block

SELECTION-SCREEN BEGIN OF BLOCK b1 WITH FRAME TITLE text-t01.

SELECT-OPTIONS: s_vbeln FOR vbak-vbeln.

SELECTION-SCREEN END OF BLOCK b1.

*--Display option - block

SELECTION-SCREEN BEGIN OF BLOCK b2 WITH FRAME TITLE text-t02.

PARAMETERS: alv_list RADIOBUTTON GROUP g1,

alv_grid RADIOBUTTON GROUP g1.

SELECTION-SCREEN END OF BLOCK b2.

*file download - block

SELECTION-SCREEN BEGIN OF BLOCK b3 WITH FRAME TITLE text-t03.

PARAMETERS: topc AS CHECKBOX,

p_file TYPE rlgrap-filename.

SELECTION-SCREEN END OF BLOCK b3.

----


  • Initialization. *

----


----


  • At Selection Screen *

----


AT SELECTION-SCREEN ON VALUE-REQUEST FOR p_file.

CALL FUNCTION 'F4_DXFILENAME_4_DYNP'

EXPORTING

dynpfield_filename = 'P_FILE'

dyname = sy-cprog

dynumb = sy-dynnr

filetype = 'P' "P-->Physical

location = 'P' "P Presentation Srever

server = space.

AT SELECTION-SCREEN ON s_vbeln.

PERFORM vbeln_validate.

----


  • Start Of Selection *

----


START-OF-SELECTION.

*-- Fetching all the required data into the internal table

PERFORM select_data.

----


  • End Of Selection *

----


END-OF-SELECTION.

IF t_itab1[] IS NOT INITIAL.

IF topc IS NOT INITIAL.

PERFORM download.

MESSAGE 'Data Download Completed' TYPE 'S'.

ENDIF.

PERFORM display.

ELSE.

MESSAGE 'No Records Found' TYPE 'I'.

ENDIF.

----


  • Top Of Page Event *

----


TOP-OF-PAGE.

&----


*& Form : select_data

&----


  • Description : Fetching all the data into the internal tables

----


  • parameters : none

*

----


FORM select_data .

SELECT vbeln

posnr

werks

lgort

INTO CORRESPONDING FIELDS OF TABLE t_itab1

FROM vbap

WHERE vbeln IN s_vbeln.

IF sy-subrc <> 0.

MESSAGE 'Enter The Valid Sales Document Number'(t04) TYPE 'I'.

EXIT.

ENDIF.

ENDFORM. " select_data

&----


*& Form : display

&----


  • decription : to display data in given format

----


  • parameters : none

----


FORM display .

IF alv_list = 'X'.

PERFORM build_fieldcat TABLES i_fieldcat[]

USING :

*-Output-field Table Len Ref fld Ref tab Heading Col_pos

'VBELN' 'T_ITAB1' 10 'VBAP' 'VBELN' '' 1,

'POSNR' 'T_ITAB1' 6 'VBAP' 'POSNR' '' 2,

'WERKS' 'T_ITAB1' 4 'VBAP' 'WERKS' '' 3,

'LGORT' 'T_ITAB1' 4 'VBAP' 'LGORT' '' 4.

CALL FUNCTION 'REUSE_ALV_LIST_DISPLAY'

EXPORTING

i_callback_program = sy-repid

  • i_callback_pf_status_set = c_pf_status

i_callback_user_command = 'USER_COMMAND '

  • it_events = t_alv_events[]

it_fieldcat = i_fieldcat[]

TABLES

t_outtab = t_itab1[]

EXCEPTIONS

program_error = 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.

ENDIF.

IF alv_grid = 'X'.

PERFORM build_fieldcat TABLES i_fieldcat[]

USING :

*-Output-field Table Len Ref fld Ref tab Heading Col_pos

'VBELN' 'T_ITAB1' 10 'VBAP' 'VBELN' '' 1,

'POSNR' 'T_ITAB1' 6 'VBAP' 'POSNR' '' 2,

'WERKS' 'T_ITAB1' 4 'VBAP' 'WERKS' '' 3,

'LGORT' 'T_ITAB1' 4 'VBAP' 'LGORT' '' 4.

CALL FUNCTION 'REUSE_ALV_GRID_DISPLAY'

EXPORTING

i_callback_program = sy-repid

  • i_callback_pf_status_set = c_pf_status

i_callback_user_command = 'USER_COMMAND '

it_fieldcat = i_fieldcat

TABLES

t_outtab = t_itab1[]

EXCEPTIONS

program_error = 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.

ENDIF.

ENDFORM. " display

&----


*& Form : vbeln_validate

&----


  • description : to validate sales document number

----


  • parameters : none

*

----


FORM vbeln_validate .

DATA: l_vbeln TYPE vbak-vbeln.

SELECT SINGLE vbeln

FROM vbak

INTO l_vbeln

WHERE vbeln IN s_vbeln.

IF sy-subrc NE 0.

MESSAGE 'ENTER THE VALID SALES DOCUMENT NO:' TYPE 'I'.

EXIT.

ENDIF.

ENDFORM. " vbeln_validate

&----


*& Form :build_fieldcat

&----


  • Description : This routine fills field-catalogue

----


  • Prameters : none

----


FORM build_fieldcat TABLES fpt_fieldcat TYPE slis_t_fieldcat_alv

USING fp_field TYPE slis_fieldname

fp_table TYPE slis_tabname

fp_length TYPE dd03p-outputlen

fp_ref_tab TYPE dd03p-tabname

fp_ref_fld TYPE dd03p-fieldname

fp_seltext TYPE dd03p-scrtext_l

fp_col_pos TYPE sy-cucol.

*-- Local data declaration

DATA: wl_fieldcat TYPE slis_fieldcat_alv.

*-- Clear WorkArea

wl_fieldcat-fieldname = fp_field.

wl_fieldcat-tabname = fp_table.

wl_fieldcat-outputlen = fp_length.

wl_fieldcat-ref_tabname = fp_ref_tab.

wl_fieldcat-ref_fieldname = fp_ref_fld.

wl_fieldcat-seltext_l = fp_seltext.

wl_fieldcat-col_pos = fp_col_pos.

*-- Update Field Catalog Table

APPEND wl_fieldcat TO fpt_fieldcat.

ENDFORM. "build_fieldcat

&----


*& Form : download

&----


  • description : To Download The Data

----


  • Parameters : none

----


FORM download .

DATA: l_file TYPE string.

l_file = p_file.

CALL FUNCTION 'GUI_DOWNLOAD'

EXPORTING

filename = l_file

filetype = 'ASC'

TABLES

data_tab = t_itab1

EXCEPTIONS

file_write_error = 1

no_batch = 2

gui_refuse_filetransfer = 3

invalid_type = 4

no_authority = 5

unknown_error = 6.

IF sy-subrc <> 0.

  • MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO

  • WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.

ENDIF.

ENDFORM. " download

thanks and regards

Rahul sharma

Former Member
0 Kudos

Hi,

See the Function Module Documentation for 'GUI_DOWNLOAD'.

And search SDN for examples.

Regards

Karthik D

former_member497886
Participant
0 Kudos

HI,

Use the below code --

open dataset <file name> for output in text mode encoding default.

loop at <internal table> .

transfer <internal table> to <filename>.

endloop.

close dataset <filename>.

Hope this will help u.

Regards,

Mohammadi.