To Download file to desktop

Hi All,
i have two checkbox options for the output,
1. create file
2.create detail report
If the Create file is checked, then i've to proceed with transfer of file and then show the selection screen data and the no of records transferred.
If the create Detailed Report is check, then proceed with the ALV display.
i.e here we should not transfer the file but display only the records and the top of page for the ALV should be displayed
If the Create file and Detailed report is both checked, the file transfer should occur and then we have to show the ALV output and the top-of-page for ALV only.
i.e here we should add the no of data transferred, Date and the physical path should be displayed in the top-of-page.
please tell me how to do.
REPORT ZPPI0036
$$----
$$ Standard routines and definitions
$$----
Include ZBSN0001.                      "Report Headers
Include ZBSN0003.                      "Common Routines
INCLUDE ZSDN0004.                      "Common Routines
$$----
$$ Tables-definitions
$$----
TABLES : ZVMATLMOVE,
         T161,
         T001W,
         T024E,
         T156,
         EKKO,
         LFA1,
         TVARV,
         MARA,
         MARC,
         EKPO,
         T024,                                        
         Z_LFA1,                                       
         M_PRCTN.                                      
$$----
$$ Internal tables definition
$$----
                                                  Begin of SIR 090216
*DATA  I_MATLMOVE LIKE ZVMATLMOVE OCCURS 0 WITH HEADER LINE.
DATA : BEGIN OF I_MATLMOVE OCCURS 0,
         MBLNR  TYPE MSEG-MBLNR,
         MJAHR  TYPE MSEG-MBLNR,
         BUDAT  TYPE MKPF-BUDAT,
         ZEILE  TYPE MSEG-ZEILE,
         BWART  TYPE MSEG-BWART,
         MATNR  TYPE MSEG-MATNR,
         WERKS  TYPE MSEG-WERKS,
         LGORT  TYPE MSEG-LGORT,                      
         LIFNR  TYPE MSEG-LIFNR,
         WAERS  TYPE MSEG-WAERS,
         MENGE  TYPE MSEG-MENGE,
         MEINS  TYPE MSEG-MEINS,
         EBELN  TYPE MSEG-EBELN,
         EBELP  TYPE MSEG-EBELP,
         PRCTR  TYPE MSEG-PRCTR,                      
       END OF I_MATLMOVE.
DATA : BEGIN OF I_OUTPUT OCCURS 0.
          INCLUDE STRUCTURE ZIP1401OUT.
DATA:  END OF I_OUTPUT.
DATA: BEGIN OF I_T156 OCCURS 0,
        BWART TYPE T156-BWART,
        SHKZG TYPE T156-SHKZG,
      END   OF I_T156.
DATA: BEGIN OF I_EKKO OCCURS 0,
        EBELN TYPE EKKO-EBELN,
        BSTYP TYPE EKKO-BSTYP,
        BSART TYPE EKKO-BSART,
        LIFNR TYPE EKKO-LIFNR,
        EKORG TYPE EKKO-EKORG,
        WAERS TYPE EKKO-WAERS,
      END   OF I_EKKO.
DATA: BEGIN OF I_EKPO OCCURS 0,
        EBELN TYPE EKPO-EBELN,
        EBELP TYPE EKPO-EBELP,
        TXZ01 TYPE EKPO-TXZ01,
        MATKL TYPE EKPO-MATKL,
        MENGE TYPE EKPO-MENGE,
        NETPR TYPE EKPO-NETPR,
        PEINH TYPE EKPO-PEINH,
      KO_PRCTR TYPE EKPO-KO_PRCTR,                    
      END   OF I_EKPO.
DATA: BEGIN OF I_MARC OCCURS 0,
        MATNR TYPE MARC-MATNR,
        WERKS TYPE MARC-WERKS,
        MAABC TYPE MARC-MAABC,
        EKGRP TYPE MARC-EKGRP,
      END   OF I_MARC.
DATA: I_MATLMOVE_TMP LIKE I_MATLMOVE OCCURS 0.
DATA: I_EKKO_TMP     LIKE I_EKKO OCCURS 0.
DATA: I_EKPO_TMP     LIKE I_EKPO OCCURS 0.
DATA: I_MARC_TMP     LIKE I_MARC OCCURS 0.
DATA: BEGIN OF I_MBEW OCCURS 0,
        MATNR TYPE MBEW-MATNR,
        BWKEY TYPE MBEW-BWKEY,
        VPRSV TYPE MBEW-VPRSV,
        VERPR TYPE MBEW-VERPR,
        STPRS TYPE MBEW-STPRS,
      END   OF I_MBEW.
DATA: BEGIN OF I_T024 OCCURS 0,
        EKGRP TYPE T024-EKGRP,
        EKNAM TYPE T024-EKNAM,
      END   OF I_T024.
DATA: BEGIN OF I_LFA1 OCCURS 0,
        LIFNR TYPE Z_LFA1-LIFNR,
        NAME1 TYPE Z_LFA1-NAME1,
      END   OF I_LFA1.
DATA: BEGIN OF I_PRCTN OCCURS 0,
        PRCTR TYPE M_PRCTN-PRCTR,
        MCTXT TYPE M_PRCTN-MCTXT,
      END   OF I_PRCTN.
$$----
$$ Variables defintions
$$----
DATA  V_FILE_CNT TYPE I.
DATA  V_LASTRUN_DATE LIKE SY-DATUM.
data  v_lastrun_time like sy-uzeit.
data  v_lastrun_time_n_date(30).
DATA  V_NAME         LIKE TVARV-NAME.
DATA  V_TEMP1(10)    TYPE P DECIMALS 4.                
$$----
$$ Constants definitions
$$----
CONSTANTS: C_VPRSV_S(1) TYPE C VALUE 'S',
           C_VPRSV_V(1) TYPE C VALUE 'V',
           C_SHKZG_H(1) TYPE C VALUE 'H'.
        Definitions needed for ALV-grid-processing
type-pools: slis,
            sscr.
         Variables defintions
data:      v_restrict      type  sscr_restrict,
           v_assn          type  sscr_***,
           v_opt_list      type  sscr_opt_list.
         ALV types
         Field catalog with field descriptions.
data:      i_fieldcat_alv    type slis_t_fieldcat_alv,
           i_list_comments   type slis_t_listheader,
           v_list_comments   like line of i_list_comments,
           i_events          type slis_t_event,
         Sort criteria for first list display.
           lt_sort_fieldcat  type slis_t_sortinfo_alv,
           ls_sort_fieldcat  type slis_sortinfo_alv,
           v_layout          type slis_layout_alv,
           v_fieldcat_alv    like line of i_fieldcat_alv,
           v_events          like line of i_events,
           v_repid           like sy-repid,
           v_variant         like disvariant,
           wa_variant        like disvariant,
           wa_variant_save   type c,
           wa_exit           type c,
           wa_repid          like sy-repid.
         Constants definitions
constants: c_x(1)            type c value 'X',
           c_alv_subtotals_summary type slis_formname
                             value 'ALV_SUBTOTALS_SUMMARY',
           c_top_of_page     type slis_formname value 'F_TOP_OF_PAGE',
           c_a(1)            type c             value 'A'.
$$----
$$ Select-options and parameters
$$----
SELECTION-SCREEN BEGIN OF BLOCK B1 WITH FRAME TITLE TEXT-003.
SELECT-OPTIONS : S_WERKS FOR T001W-WERKS,
                 S_EKORG FOR T024E-EKORG,
                 S_LIFNR FOR LFA1-LIFNR,
                 S_MATNR FOR MARA-MATNR,
                 S_BWART FOR T156-BWART,
                 S_EBELN FOR EKKO-EBELN,
                 S_BSTYP FOR T161-BSTYP NO INTERVALS,
                 S_BSART FOR T161-BSART NO INTERVALS.
PARAMETERS:      P_WAERS LIKE T001-WAERS DEFAULT 'USD' OBLIGATORY.
SELECTION-SCREEN END OF BLOCK B1.
SELECTION-SCREEN BEGIN OF BLOCK E WITH FRAME.
PARAMETERS: P_FILE AS CHECKBOX,
            P_REPORT AS CHECKBOX.
SELECTION-SCREEN END OF BLOCK E.
selection-screen begin of block file01 with frame.
PARAMETERS: P_FILEID(6).
PARAMETERS: P_LF_01 LIKE FILETEXTCI-FILEINTERN
                    DEFAULT 'Z_IP1401_RECEIPT_EXTRACT',
            P_PF_01 LIKE V_FILENACI-FILEEXTERN.
selection-screen end of block file01.
SELECTION-SCREEN BEGIN OF BLOCK DT WITH FRAME.
selection-screen skip 1.
SELECTION-SCREEN COMMENT 1(65) TEXT-D00.
PARAMETERS: P_DATE LIKE SY-DATUM.
selection-screen skip 1.
SELECTION-SCREEN END OF BLOCK DT.
selection-screen begin of block sb with frame.
selection-screen skip 1.
selection-screen comment 10(65) text-X00.
selection-screen skip 1.
selection-screen comment 10(65) text-X01.
selection-screen skip 1.
selection-screen comment 10(65) text-X02.
selection-screen end of block sb.
$$----
$$ initialization.
$$----
initialization.
    PERFORM GET_FILE_NAME USING P_LF_01 P_FILEID '' CHANGING P_PF_01.
$$----
$$ At Selection-Screen.
$$----
At Selection-Screen.
IF P_FILE IS INITIAL AND P_REPORT IS INITIAL.
    MESSAGE E100.
  endif.
If not p_lf_01 is initial.
    PERFORM GET_FILE_NAME USING P_LF_01 P_FILEID '' CHANGING P_PF_01.
  endif.
$$----
$$ Start-of-selection.
$$----
Start-of-selection.
  IF P_FILE = 'X'.
   PERFORM OPEN_DATASETS.
  ENDIF.
  CLEAR V_LASTRUN_DATE.
  CONCATENATE SY-CPROG P_FILEID INTO V_NAME.
  IF P_DATE IS INITIAL.
    PERFORM GET_LASTRUN_DATE.
  ELSE.
    V_LASTRUN_DATE = P_DATE.
  ENDIF.
  PERFORM SELECT_T156.
  PERFORM SELECT_ZVMATLMOVE.
  IF NOT I_MATLMOVE[] IS INITIAL.
    PERFORM SELECT_SUPPORTING_DATA.
    PERFORM PROCESS_DATA.
  ENDIF.
Prepare the data to display the report as ALV GRID.
  perform process_alv_grid.
$$----
$$ End-of-selection.
$$----
End-of-selection.
to change the sorting sequence for the output
  SORT I_OUTPUT BY MATNR BUDAT MJAHR.                   
  IF P_FILE = 'X'.
   PERFORM WRITE_TO_FILE.
  ENDIF.
  IF P_REPORT = 'X'.
  PERFORM WRITE_TO_REPORT.
  ENDIF.
Perform Close_datasets.
PERFORM UPDATE_TVARV.
PERFORM ZSDN0004_PRINT_SELECT_OPTIONS
         USING SY-CPROG ' '.
PERFORM FINAL_STATS.
$$----
$$ Top-of-page.
$$----
Top-of-page.
  FORMAT COLOR 2.
  PERFORM ZBSN0001_STANDARD_HEADER USING SPACE SYST-TITLE SPACE SPACE.
  FORMAT COLOR OFF.
*Top-of-page.
form f_top_of_page.
  clear  v_list_comments.
  refresh i_list_comments.
  v_list_comments-typ = 'H'.
  move: text-h01 to v_list_comments-info.
  append  v_list_comments  to  i_list_comments .
  clear  v_list_comments .
  call function 'REUSE_ALV_COMMENTARY_WRITE'
    exporting
      it_list_commentary       = i_list_comments
  I_LOGO                   =
  I_END_OF_LIST_GRID       =
endform.                                     "f_top_of_page.
$$----
$$ Form Open_Datasets.
$$----
*Form Open_Datasets.
  perform open_file using p_pf_01 'OUTPUT   ' 'TEXT  '.
*Endform.
$$----
$$ Form  GET_LASTRUN_DATE
$$----
FORM GET_LASTRUN_DATE.
Get the last run date from TVARV
  SELECT SINGLE LOW FROM TVARV
                    INTO TVARV-LOW
                    WHERE NAME = V_NAME
                      AND TYPE = 'P'
                      AND NUMB = 0.
  IF SY-SUBRC NE 0.
  If it does not exist then a full refresh will be sent
  ELSE.
    V_LASTRUN_DATE = TVARV-LOW+0(8).
  ENDIF.
ENDFORM.
$$----
$$ Form  SELECT_T156
$$----
FORM SELECT_T156 .
Get all of the info on the movement types that will be selected
  SELECT BWART              "Movement Type
         SHKZG              "Debit/Credit Indicator
    FROM T156
    INTO TABLE I_T156
    WHERE BWART IN S_BWART.
ENDFORM.                    " SELECT_T156
$$----
$$ Form  SELECT_ZVMATLMOVE
$$----
FORM SELECT_ZVMATLMOVE .
Get Material Document, Year of Material Doc, Item in Material Doc,
PO number, PO line item, Posting Date, Movement Type, Plant,
Purchasing Org, Material Group, Material number, Vendor Id,
Currency Key, Quantity Recieved, UOM, Storage location from View of
Material Doc Header and Items to the internal table I_MATLMOVE
  SELECT MBLNR
         MJAHR
         BUDAT
         ZEILE
         BWART                                         
         MATNR
         WERKS
         LGORT                                         
         LIFNR
         WAERS
         MENGE
         MEINS
         EBELN
         EBELP
         PRCTR                                         
    FROM ZVMATLMOVE
    INTO TABLE I_MATLMOVE
   WHERE BUDAT >= V_LASTRUN_DATE
     AND BWART IN S_BWART
     AND MATNR IN S_MATNR
     AND WERKS IN S_WERKS
     AND LIFNR IN S_LIFNR
     AND EBELN IN S_EBELN.
ENDFORM.                    " SELECT_ZVMATLMOVE
$$----
$$ Form  SELECT_SUPPORTING_DATA
$$----
FORM SELECT_SUPPORTING_DATA .
  I_MATLMOVE_TMP[] = I_MATLMOVE[].
  SORT I_MATLMOVE_TMP BY EBELN.
  DELETE ADJACENT DUPLICATES FROM I_MATLMOVE_TMP COMPARING EBELN.
Get Purchasing org, Currency, Account No, Purchasing doc category,
Purchasing Document Type from Purchasing Document Header table
  SELECT EBELN          "Purchasing Document Number
         BSTYP          "Purchasing document category
         BSART          "Purchasing Document Type
         LIFNR          "Account Number of the Vendor
         EKORG          "Purchasing Organization
         WAERS          "Currency Key
    FROM EKKO
    INTO TABLE I_EKKO
     FOR ALL ENTRIES IN I_MATLMOVE_TMP
   WHERE EBELN = I_MATLMOVE_TMP-EBELN
     AND EKORG IN S_EKORG
     AND BSART IN S_BSART
     AND BSTYP IN S_BSTYP.
  CLEAR   I_MATLMOVE_TMP.
  REFRESH I_MATLMOVE_TMP.
  I_MATLMOVE_TMP[] = I_MATLMOVE[].
  SORT I_MATLMOVE_TMP BY EBELN EBELP.
  DELETE ADJACENT DUPLICATES
             FROM I_MATLMOVE_TMP COMPARING EBELN EBELP.
Get the material group and the net price from the PO Line item
  SELECT EBELN            "Purchasing Document Number
         EBELP            "Item Number of Purchasing Document
         TXZ01            "Short text
         MATKL            "Material Group
         MENGE            "Purchase order quantity
         NETPR            "Net price in purchasing document
         PEINH            "Price unit
       KO_PRCTR         "Profit Center                
    FROM EKPO
    INTO TABLE I_EKPO
     FOR ALL ENTRIES IN I_MATLMOVE_TMP
   WHERE EBELN = I_MATLMOVE_TMP-EBELN
     AND EBELP = I_MATLMOVE_TMP-EBELP.
  CLEAR   I_MATLMOVE_TMP.
  REFRESH I_MATLMOVE_TMP.
  I_MATLMOVE_TMP[] = I_MATLMOVE[].
  SORT I_MATLMOVE_TMP BY MATNR WERKS.
  DELETE ADJACENT DUPLICATES
             FROM I_MATLMOVE_TMP COMPARING MATNR WERKS.
Get the Purchasing Group from the Plant Data for Material table
  SELECT MATNR            "Material Number
         WERKS            "Plant
         MAABC            "ABC indicator
         EKGRP            "Purchasing Group
    FROM MARC
    INTO TABLE I_MARC
     FOR ALL ENTRIES IN I_MATLMOVE_TMP
   WHERE MATNR = I_MATLMOVE_TMP-MATNR
     AND WERKS = I_MATLMOVE_TMP-WERKS.
Get the standard price from the Material Valuation table
  SELECT MATNR            "Material Number
         BWKEY            "Valuation area
         VPRSV            "Price Control Indicator
         VERPR            "Moving Average Price
         STPRS            "Standard Price
    FROM MBEW
    INTO TABLE I_MBEW
     FOR ALL ENTRIES IN I_MATLMOVE_TMP
   WHERE MATNR = I_MATLMOVE_TMP-MATNR
     AND BWKEY = I_MATLMOVE_TMP-WERKS.
  IF NOT I_MARC[] IS INITIAL.
    I_MARC_TMP[] = I_MARC[].
    SORT I_MARC_TMP BY EKGRP.
    DELETE ADJACENT DUPLICATES
               FROM I_MARC_TMP COMPARING EKGRP.
  Get the Buyer name from the purchasing groups table
    SELECT EKGRP            "Purchasing Group
           EKNAM            "Description of purchasing group
      FROM T024
      INTO TABLE I_T024
       FOR ALL ENTRIES IN I_MARC_TMP
     WHERE EKGRP = I_MARC_TMP-EKGRP.
  ENDIF.
  IF NOT I_EKKO[] IS INITIAL.
    I_EKKO_TMP[] = I_EKKO[].
    SORT I_EKKO_TMP BY LIFNR.
    DELETE ADJACENT DUPLICATES
               FROM I_EKKO_TMP COMPARING LIFNR.
  Get the Vendor name from the Vendor Master (General Data subset)
    SELECT LIFNR            "Account Number of Vendor or Creditor
           NAME1            "Name 1
      FROM Z_LFA1
      INTO TABLE I_LFA1
       FOR ALL ENTRIES IN I_EKKO_TMP
     WHERE LIFNR = I_EKKO_TMP-LIFNR.
  ENDIF.
IF NOT I_EKPO[] IS INITIAL.
   I_EKPO_TMP[] = I_EKPO[].
   SORT I_EKPO_TMP BY KO_PRCTR.
   DELETE ADJACENT DUPLICATES
              FROM I_EKPO_TMP COMPARING KO_PRCTR.
    I_MATLMOVE_TMP[] = I_MATLMOVE[].
    SORT I_MATLMOVE_TMP BY PRCTR.
    DELETE ADJACENT DUPLICATES
               FROM I_MATLMOVE_TMP COMPARING PRCTR.
                                                    End of SIR 301081
  Get the Profit center name from the Generated view for matchcodeID
  PRCT-N
    SELECT PRCTR            "Profit Center
           MCTXT            "Search term for matchcode search
      FROM M_PRCTN
      INTO TABLE I_PRCTN
     FOR ALL ENTRIES IN I_EKPO_TMP                  
   WHERE PRCTR = I_EKPO_TMP-KO_PRCTR.               
       FOR ALL ENTRIES IN I_MATLMOVE_TMP              
     WHERE PRCTR = I_MATLMOVE_TMP-PRCTR.              
ENDIF.                                             
  CLEAR: I_MATLMOVE_TMP,
         I_EKKO_TMP,
         I_EKPO_TMP,
         I_MARC_TMP.
  REFRESH: I_MATLMOVE_TMP,
           I_EKKO_TMP,
           I_EKPO_TMP,
           I_MARC_TMP.
ENDFORM.                    " SELECT_SUPPORTING_DATA
$$----
$$ Form  PROCESS_DATA
$$----
FORM PROCESS_DATA .
  SORT I_EKKO  BY EBELN.
  SORT I_MARC  BY MATNR WERKS.
  SORT I_EKPO  BY EBELN EBELP.
  SORT I_MBEW  BY MATNR BWKEY.
  SORT I_T024  BY EKGRP.
  SORT I_LFA1  BY LIFNR.
  SORT I_PRCTN BY PRCTR.
Loop the internal I_MATLMOVE and move the corresponding values to
the internal table I_OUTPUT
  LOOP AT I_MATLMOVE.
    CLEAR V_TEMP1.
  Move the Purchasing document category, Purchasing Document Type,
  Account Number of the Vendor , Purchasing Organization from table
  Purchasing Document Header to the internal table I_OUTPUT
    CLEAR I_EKKO.
    READ TABLE I_EKKO WITH KEY EBELN = I_MATLMOVE-EBELN
                               BINARY SEARCH.
    IF SY-SUBRC EQ 0.
      I_OUTPUT-BSTYP    = I_EKKO-BSTYP.
      I_OUTPUT-BSART    = I_EKKO-BSART.
      I_OUTPUT-LIFNR    = I_EKKO-LIFNR.
      I_OUTPUT-EKORG    = I_EKKO-EKORG.
    Move the Vendor name from view Vendor Master(General Data subset)
    to the internal table I_OUTPUT
      CLEAR I_LFA1.
      READ TABLE I_LFA1 WITH KEY LIFNR = I_EKKO-LIFNR
                                 BINARY SEARCH.
      IF SY-SUBRC EQ 0.
        I_OUTPUT-LIFNR1 = I_LFA1-LIFNR.
        I_OUTPUT-NAME1  = I_LFA1-NAME1.
      ENDIF.
    ENDIF.
  Move the ABC indicator,Purchasing Group from table Plant Data for
  Material to the internal table I_OUTPUT
    CLEAR I_MARC.
    READ TABLE I_MARC WITH KEY MATNR = I_MATLMOVE-MATNR
                               WERKS = I_MATLMOVE-WERKS
                               BINARY SEARCH.
    IF SY-SUBRC EQ 0.
      I_OUTPUT-MAABC   = I_MARC-MAABC.
      I_OUTPUT-EKGRP   = I_MARC-EKGRP.
    Move the Buyer name from table Purchasing Group into the internal
    table I_OUTPUT
      CLEAR I_T024.
      READ TABLE I_T024 WITH KEY EKGRP = I_MARC-EKGRP
                                 BINARY SEARCH.
      IF SY-SUBRC EQ 0.
        I_OUTPUT-EKNAM = I_T024-EKNAM.
      ENDIF.
    ENDIF.
  Move the Material Description, Material Group, Purchase order qty,
  Net price in purchasing doc, Profit Center from the table
  Purchasing Document Item to the internal table I_OUTPUT
    CLEAR I_EKPO.
    READ TABLE I_EKPO WITH KEY EBELN = I_MATLMOVE-EBELN
                               EBELP = I_MATLMOVE-EBELP
                               BINARY SEARCH.
    IF SY-SUBRC EQ 0.
      I_OUTPUT-TXZ01    = I_EKPO-TXZ01.
      I_OUTPUT-MATKL    = I_EKPO-MATKL.
      I_OUTPUT-MENGE1   = I_EKPO-MENGE.
    I_OUTPUT-KO_PRCTR = I_EKPO-KO_PRCTR.            
    Convert to the currency of the input parameter
      PERFORM CONVERT_CURRENCY USING I_EKKO-WAERS
                                     P_WAERS
                                     I_EKPO-NETPR
                            CHANGING I_EKPO-NETPR.
      V_TEMP1 = I_EKPO-NETPR / I_EKPO-PEINH.
    Deleting commas to the purchase order quantity
      IF I_OUTPUT-MENGE1 IS NOT INITIAL.
        PERFORM DELETE_COMMAS CHANGING I_OUTPUT-MENGE1.
        SHIFT I_OUTPUT-MENGE1 RIGHT CIRCULAR.
        CONDENSE I_OUTPUT-MENGE1 NO-GAPS.
        SHIFT I_OUTPUT-MENGE1 RIGHT DELETING TRAILING SPACE.
      ENDIF.
    Move the Profit Center name (text) from Generated view for
    matchcode ID PRCT-N to the internal table I_OUTPUT
      CLEAR I_PRCTN.
                                                  Begin of SIR 301081
    READ TABLE I_PRCTN WITH KEY PRCTR = I_EKPO-KO_PRCTR
                                BINARY SEARCH.
      READ TABLE I_PRCTN WITH KEY PRCTR = I_MATLMOVE-PRCTR
                                  BINARY SEARCH.
                                                    End of SIR 301081
      IF SY-SUBRC EQ 0.
        I_OUTPUT-MCTXT = I_PRCTN-MCTXT.
      ENDIF.
    ENDIF.
  Move the Standard Price from table Material Valuation to the
  internal table I_OUTPUT
    CLEAR I_MBEW.
    READ TABLE I_MBEW WITH KEY MATNR = I_MATLMOVE-MATNR
                               BWKEY = I_MATLMOVE-WERKS
                               BINARY SEARCH.
    IF SY-SUBRC EQ 0.
    To check the Price control indicator
    S for Standard Price
    V for Moving price
      IF I_MBEW-VPRSV EQ C_VPRSV_S.
      Convert to the currency of the input parameter
        PERFORM CONVERT_CURRENCY USING I_EKKO-WAERS
                                       P_WAERS
                                       I_MBEW-STPRS
                              CHANGING I_MBEW-STPRS.
        I_OUTPUT-STPRS = I_MBEW-STPRS.
      ELSEIF I_MBEW-VPRSV EQ C_VPRSV_V.
      Convert to the currency of the input parameter
        PERFORM CONVERT_CURRENCY USING I_EKKO-WAERS
                                       P_WAERS
                                       I_MBEW-VERPR
                              CHANGING I_MBEW-VERPR.
        I_OUTPUT-STPRS = I_MBEW-VERPR.
      ENDIF.
    ENDIF.
  Move the PO number, Material Document, Year of Material Doc,
  Item in Material Doc, PO line item, Plant, Material Number,
  Vendor Id, UOM, Currency Key, Movement Type, Storage location,
  Profit Center from view View of Material Doc Header and Items
  to the internal table I_OUTPUT
    I_OUTPUT-EBELN = I_MATLMOVE-EBELN.
    I_OUTPUT-MBLNR = I_MATLMOVE-MBLNR.
    I_OUTPUT-MJAHR = I_MATLMOVE-MJAHR.
    I_OUTPUT-ZEILE = I_MATLMOVE-ZEILE.
    I_OUTPUT-EBELP = I_MATLMOVE-EBELP.
    I_OUTPUT-WERKS = I_MATLMOVE-WERKS.
    I_OUTPUT-MATNR = I_MATLMOVE-MATNR.
    I_OUTPUT-LIFNR = I_MATLMOVE-LIFNR.
    I_OUTPUT-MEINS = I_MATLMOVE-MEINS.
    I_OUTPUT-WAERS = P_WAERS.
    I_OUTPUT-BWART = I_MATLMOVE-BWART.
    I_OUTPUT-LGORT = I_MATLMOVE-LGORT.
    I_OUTPUT-KO_PRCTR = I_MATLMOVE-PRCTR.              
    WRITE I_MATLMOVE-BUDAT TO I_OUTPUT-BUDAT.
  Multiply amt and qty by -1 if the movement type is a credit
    CLEAR I_T156.
    READ TABLE I_T156 WITH KEY BWART = I_MATLMOVE-BWART.
    IF I_T156-SHKZG = C_SHKZG_H.
      V_TEMP1 = V_TEMP1 * -1.
      I_MATLMOVE-MENGE = I_MATLMOVE-MENGE * -1.
      WRITE I_MATLMOVE-MENGE TO I_OUTPUT-MENGE UNIT I_MATLMOVE-MEINS.
      PERFORM DELETE_COMMAS CHANGING I_OUTPUT-MENGE.
      SHIFT I_OUTPUT-MENGE RIGHT CIRCULAR.
      CONDENSE I_OUTPUT-MENGE NO-GAPS.
      SHIFT I_OUTPUT-MENGE RIGHT DELETING TRAILING SPACE.
    ELSE.
      WRITE I_MATLMOVE-MENGE TO I_OUTPUT-MENGE UNIT I_MATLMOVE-MEINS.
      PERFORM DELETE_COMMAS CHANGING I_OUTPUT-MENGE.
    ENDIF.
  Formatting the PO unit price
    I_OUTPUT-NETPR = V_TEMP1.
    SHIFT I_OUTPUT-NETPR RIGHT CIRCULAR.
    CONDENSE I_OUTPUT-NETPR NO-GAPS.
    SHIFT I_OUTPUT-NETPR RIGHT DELETING TRAILING SPACE.
    APPEND I_OUTPUT.
    CLEAR I_OUTPUT.
  ENDLOOP.
ENDFORM.                    " PROCESS_DATA
$$----
$$ Form  WRITE_TO_FILE
$$----
*FORM WRITE_TO_FILE.
LOOP AT I_OUTPUT.
   V_FILE_CNT = V_FILE_CNT + 1.
   TRANSFER I_OUTPUT TO P_PF_01 LENGTH 312.
ENDLOOP.
*ENDFORM.
$$----
$$ Form  WRITE_TO_REPORT
$$----
*FORM WRITE_TO_REPORT.
PERFORM WRITE_HEADINGS.
LOOP AT I_OUTPUT.
   WRITE : / I_OUTPUT-MBLNR.
   WRITE I_OUTPUT-MJAHR.
   WRITE I_OUTPUT-ZEILE.
   WRITE I_OUTPUT-EBELN.
   WRITE I_OUTPUT-EBELP.
   WRITE I_OUTPUT-BUDAT.
   WRITE I_OUTPUT-WERKS.
   WRITE I_OUTPUT-EKORG.
   WRITE I_OUTPUT-MATKL.
   WRITE I_OUTPUT-MATNR.
   WRITE I_OUTPUT-EKGRP.
   WRITE I_OUTPUT-LIFNR.
   WRITE I_OUTPUT-NETPR.
   WRITE I_OUTPUT-WAERS.
   WRITE I_OUTPUT-MENGE.
   WRITE I_OUTPUT-MEINS.
   WRITE I_OUTPUT-MENGE1.
   WRITE I_OUTPUT-MAABC.
   WRITE I_OUTPUT-STPRS.
   WRITE I_OUTPUT-TXZ01.
   WRITE I_OUTPUT-EKNAM.
   WRITE I_OUTPUT-LIFNR1.
   WRITE I_OUTPUT-NAME1.
   WRITE I_OUTPUT-KO_PRCTR.
   WRITE I_OUTPUT-MCTXT.
   WRITE I_OUTPUT-BSTYP.
   WRITE I_OUTPUT-BSART.
   WRITE I_OUTPUT-BWART.
   WRITE I_OUTPUT-LGORT.
ENDLOOP.
NEW-PAGE.
*ENDFORM.
$$----
$$ Form Close_Datasets.
$$----
*Form Close_Datasets.
  Perform Close_file using p_pf_01.
*Endform.
$$----
$$ Form  UPDATE_TVARV
$$----
*FORM UPDATE_TVARV.
    TVARV-NAME = V_NAME.
    TVARV-TYPE = 'P'.
    TVARV-NUMB = 0.
    TVARV-LOW = SY-DATLO.
    MODIFY TVARV.
*ENDFORM.
$$----
$$ Form  FINAL_STATS
$$----
*FORM FINAL_STATS.
   WRITE: / 'FINAL STATS:'(018).
   WRITE: /'--------------'.
   IF P_FILE = 'X'.
     WRITE: / 'File Created - '(015), P_PF_01.
     WRITE: / 'Nbr of Records written to the file - '(016).
     WRITE: V_FILE_CNT.
   ELSE.
     WRITE: / 'No File Created.'(017).
   ENDIF.
   SKIP.
   IF P_DATE IS INITIAL.
     WRITE: / 'Last rundate before this run - '(001), V_LASTRUN_DATE.
   ENDIF.
   WRITE: / 'New Last rundate             - '(002)     , SY-DATLO.
*ENDFORM.
$$----
$$ Form  CONVERT_CURRENCY
$$----
FORM CONVERT_CURRENCY USING    P_IN_WAERS
                               P_OUT_WAERS
                               P_IN_AMT
                      CHANGING P_OUT_AMT.
  IF P_IN_WAERS = P_OUT_WAERS.
    P_OUT_AMT = P_IN_AMT.
  ELSE.
    CALL FUNCTION 'CONVERT_TO_LOCAL_CURRENCY'
         EXPORTING
              DATE             = SY-DATUM
              FOREIGN_AMOUNT   = P_IN_AMT
              FOREIGN_CURRENCY = P_IN_WAERS
              LOCAL_CURRENCY   = P_OUT_WAERS
            type_of_rate     = c_type
          IMPORTING
              LOCAL_AMOUNT     = P_OUT_AMT
         EXCEPTIONS
               NO_RATE_FOUND    = 1
              OVERFLOW         = 2.
  ENDIF.
ENDFORM.
$$----
$$ Form  DELETE_COMMAS
$$----
FORM DELETE_COMMAS CHANGING P_AMT.
    DO.
      REPLACE ',' WITH SPACE INTO P_AMT.
      IF SY-SUBRC NE 0.
        EXIT.
      ENDIF.
    ENDDO.
    CONDENSE P_AMT NO-GAPS.
    SHIFT P_AMT RIGHT DELETING TRAILING SPACE.
ENDFORM.                    "DELETE_COMMASENDFORM.
$$----
$$ Form  WRITE_HEADINGS
$$----
*FORM WRITE_HEADINGS.
ULINE.
FORMAT COLOR 1.
WRITE 'Matl Doc. '(004).
WRITE 'Year'(005).
WRITE 'Item'(006).
WRITE 'PO Nbr    '(007).
WRITE 'Item '(008).
WRITE 'Post Date '(009).
WRITE 'Plnt'(010).
WRITE 'POrg'(011).
WRITE 'Matl Grp '(012).
WRITE 'Material          '(013).
WRITE 'PGp'(014).
WRITE 'Vendor    '(019).
WRITE '            Price '(020).
WRITE 'Ckey'(021).
WRITE '              Qty'(022).
WRITE 'UOM'(023).
                                                  Begin of SIR 300589
WRITE 'Purchase order Qty'(024).
WRITE 'ABC Inventory Indicator'(025).
WRITE 'Standard Price'(026).
WRITE 'Material Desc'(027).
WRITE 'Buyer Name'(028).
WRITE 'Vendor ID'(029).
WRITE 'Vendor Name'(030).
WRITE 'Profit Center'(031).
WRITE 'Profit Center Name'(032).
WRITE 'Purchasing Doc Category'(033).
WRITE 'Purchasing Doc Type'(034).
WRITE 'Movement Type'(035).
WRITE 'Storage Location'(036).
                                                    End of SIR 300589
FORMAT COLOR OFF.
*ENDFORM.
                                                  Begin Of SIR-301278
*&      Form  process_alv_grid
      To process the data for ALV GRID  display
FORM process_alv_grid .
To Maintain Layout settings.
  perform build_layout.
To display column headings.
  perform fill_fieldcatalog.
To build the alv events for output
  perform event_build.
To display the output in a ALV grid
  perform grid_display.
ENDFORM.                    " process_alv_grid
*&      Form  build_layout
      To fill the layout characteristics for output
FORM build_layout .
Move the report title
  clear v_layout.
  v_layout-detail_titlebar = sy-title.
ENDFORM.                    " build_layout
*&      Form  event_build
       To build the alv events for output
FORM event_build .
refresh i_events.
  clear   v_events.
  call function 'REUSE_ALV_EVENTS_GET'
    exporting
      i_list_type = 0
    importing
      et_events   = i_events.
  read table i_events with key name = slis_ev_top_of_page
                                           into v_events.
  if sy-subrc = 0.
    move c_top_of_page to v_events-form.
    modify i_events from v_events index sy-tabix.
  endif.
  read table i_events with key name = slis_ev_subtotal_text
                                             into v_events.
  if sy-subrc = 0.
    move c_alv_subtotals_summary to v_events-form.
    modify i_events from v_events index sy-tabix.
  endif.
ENDFORM.                    " event_build
*&      Form  fill_fieldcatalog
     This subroutine builds the fieldcatalog for output
FORM fill_fieldcatalog .
refresh: i_fieldcat_alv[].
  clear v_fieldcat_alv.
  v_fieldcat_alv-tabname      = 'I_OUTPUT'.
  v_fieldcat_alv-fieldname    = 'MBLNR'.
  v_fieldcat_alv-reptext_ddic = text-001.
  v_fieldcat_alv-col_pos      = 1.
  append v_fieldcat_alv to i_fieldcat_alv.
  clear v_fieldcat_alv.
  v_fieldcat_alv-tabname      = 'I_OUTPUT'.
  v_fieldcat_alv-fieldname    = 'MJAHR'.
  v_fieldcat_alv-reptext_ddic = text-002.
  v_fieldcat_alv-col_pos      = 2.
  append v_fieldcat_alv to i_fieldcat_alv.
  clear v_fieldcat_alv.
  v_fieldcat_alv-tabname      = 'I_OUTPUT'.
  v_fieldcat_alv-fieldname    = 'ZEILE'.
  v_fieldcat_alv-reptext_ddic = text-003.
  v_fieldcat_alv-col_pos      = 3.
  append v_fieldcat_alv to i_fieldcat_alv.
  clear v_fieldcat_alv.
  v_fieldcat_alv-tabname      = 'I_OUTPUT'.
  v_fieldcat_alv-fieldname    = 'EBELN'.
  v_fieldcat_alv-reptext_ddic = text-004.
  v_fieldcat_alv-col_pos      = 4.
  append v_fieldcat_alv to i_fieldcat_alv.
  clear v_fieldcat_alv.
  v_fieldcat_alv-tabname      = 'I_OUTPUT'.
  v_fieldcat_alv-fieldname    = 'EBELP'.
  v_fieldcat_alv-reptext_ddic = text-005.
  v_fieldcat_alv-col_pos      = 5.
  append v_fieldcat_alv to i_fieldcat_alv.
  clear v_fieldcat_alv.
  v_fieldcat_alv-tabname      = 'I_OUTPUT'.
  v_fieldcat_alv-fieldname    = 'BUDAT'.
  v_fieldcat_alv-reptext_ddic = text-006.
  v_fieldcat_alv-col_pos      = 6.
  append v_fieldcat_alv to i_fieldcat_alv.
  clear v_fieldcat_alv.
  v_fieldcat_alv-tabname      = 'I_OUTPUT'.
  v_fieldcat_alv-fieldname    = 'WERKS'.
  v_fieldcat_alv-reptext_ddic = text-007.
  v_fieldcat_a

Hi Priya,
u can download the data from dictionary table to ur pc/dektop by using three function modules.
1.DOWNLOAD
2.WS_DOWNLOAD
3.GUI_DOWNLOAD
i did a small prg.just hv a look and if it is possible change this to ur require output.
TABLES: VBAK,VBAP.
DATA: BEGIN OF I_VBAK OCCURS 0,
      VBELN LIKE VBAK-VBELN,
      ERDAT LIKE VBAK-ERDAT,
      ERNAM LIKE VBAK-ERNAM,
      AUDAT LIKE VBAK-AUDAT,
      VBTYP LIKE VBAK-VBTYP,
      END OF I_VBAK.
DATA: BEGIN OF I_VBAP OCCURS 0,
      VBELN LIKE VBAP-VBELN,
      POSNR LIKE VBAP-POSNR,
      MATNR LIKE VBAP-MATNR,
      CHARG LIKE VBAP-CHARG,
      MATKL LIKE VBAP-MATKL,
      END OF I_VBAP.
DATA: BEGIN OF IT_VBAK OCCURS 0,
      VBELN LIKE VBAK-VBELN,
      ERDAT LIKE VBAK-ERDAT,
      ERNAM LIKE VBAK-ERNAM,
      AUDAT LIKE VBAK-AUDAT,
      VBTYP LIKE VBAK-VBTYP,
      POSNR LIKE VBAP-POSNR,
      MATNR LIKE VBAP-MATNR,
      CHARG LIKE VBAP-CHARG,
      MATKL LIKE VBAP-MATKL,
      END OF IT_VBAK.
SELECT VBELN ERDAT ERNAM AUDAT VBTYP FROM VBAK INTO TABLE I_VBAK.
SELECT VBELN POSNR MATNR CHARG MATKL FROM VBAP INTO TABLE I_VBAP.
SORT: I_VBAK BY VBELN,I_VBAP BY VBELN.
LOOP AT I_VBAK.
READ TABLE I_VBAP WITH KEY VBELN = I_VBAK-VBELN BINARY SEARCH.
IF SY-SUBRC = 0.
  MOVE I_VBAK-VBELN TO IT_VBAK-VBELN.
  MOVE I_VBAK-ERDAT TO IT_VBAK-ERDAT.
  MOVE I_VBAK-ERNAM TO IT_VBAK-ERNAM.
  MOVE I_VBAK-AUDAT TO IT_VBAK-AUDAT.
  MOVE I_VBAK-VBTYP TO IT_VBAK-VBTYP.
  MOVE I_VBAP-POSNR TO IT_VBAK-POSNR.
  MOVE I_VBAP-MATNR TO IT_VBAK-MATNR.
  MOVE I_VBAP-CHARG TO IT_VBAK-CHARG.
  MOVE I_VBAP-MATKL TO IT_VBAK-MATKL.
APPEND IT_VBAK.
ENDIF.
ENDLOOP.
*& IT ASKS THE CONFIRMATION FOR THE FILE FORMATE,WE CAN CHANGE THE FILENAME DYNAMICALLY(e.g DOC-TXT,XLS)
*CALL FUNCTION 'DOWNLOAD'
EXPORTING
  BIN_FILESIZE                  = ' '
  CODEPAGE                      = ' '
  FILENAME                      = 'D:\C1.TXT'
  FILETYPE                      = 'DAT'   "ASC is also another format
  ITEM                          = ' '
  MODE                          = ' '
  WK1_N_FORMAT                  = ' '
  WK1_N_SIZE                    = ' '
  WK1_T_FORMAT                  = ' '
  WK1_T_SIZE                    = ' '
  FILEMASK_MASK                 = '.TXT'
  FILEMASK_TEXT                 = ' '
  FILETYPE_NO_CHANGE            = 'X'
  FILEMASK_ALL                  = ' '
  FILETYPE_NO_SHOW              = 'X'     "THIS WILL NOT SHOW THE FILE TYPE(DAT) WHILE CONFIRMATION OF FILE NAME
  SILENT                        = 'S'
  COL_SELECT                    = ' '
  COL_SELECTMASK                = ' '
  NO_AUTH_CHECK                 = ' '
IMPORTING
  ACT_FILENAME                  =
  ACT_FILETYPE                  =
  FILESIZE                      =
  CANCEL                        =
TABLES
   DATA_TAB                      = IT_VBAK
  FIELDNAMES                    =
EXCEPTIONS
  INVALID_FILESIZE              = 1
  INVALID_TABLE_WIDTH           = 2
  INVALID_TYPE                  = 3
  NO_BATCH                      = 4
  UNKNOWN_ERROR                 = 5
  GUI_REFUSE_FILETRANSFER       = 6
  OTHERS                        = 7
*IF SY-SUBRC <> 0.
MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
        WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
*ENDIF.
*& this will not ask for the confirmation for the filename
*CALL FUNCTION 'WS_DOWNLOAD'
EXPORTING
  BIN_FILESIZE                  = ' '
  CODEPAGE                      = ' '
  FILENAME                      = 'D:\C2.DOC'
  FILETYPE                      = 'DAT'
  MODE                          = ' '
  WK1_N_FORMAT                  = ' '
  WK1_N_SIZE                    = ' '
  WK1_T_FORMAT                  = ' '
  WK1_T_SIZE                    = ' '
  COL_SELECT                    = ' '
  COL_SELECTMASK                = ' '
  NO_AUTH_CHECK                 = ' '
IMPORTING
  FILELENGTH                    =
TABLES
   DATA_TAB                      = IT_VBAK
  FIELDNAMES                    =
EXCEPTIONS
  FILE_OPEN_ERROR               = 1
  FILE_WRITE_ERROR              = 2
  INVALID_FILESIZE              = 3
  INVALID_TYPE                  = 4
  NO_BATCH                      = 5
  UNKNOWN_ERROR                 = 6
  INVALID_TABLE_WIDTH           = 7
  GUI_REFUSE_FILETRANSFER       = 8
  CUSTOMER_ERROR                = 9
  NO_AUTHORITY                  = 10
  OTHERS                        = 11
*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 'GUI_DOWNLOAD'
  EXPORTING
  BIN_FILESIZE                    =
    FILENAME                        = 'D:\C5.DOC'
   FILETYPE                        = 'ASC'  "Separate Columns by Tabs in Case of ASCII Download
  APPEND                          = ' '
   WRITE_FIELD_SEPARATOR           = 'X'
  HEADER                          = '00'
  TRUNC_TRAILING_BLANKS           = ' '
  WRITE_LF                        = 'X'
  COL_SELECT                      = ' '
  COL_SELECT_MASK                 = ' '
  DAT_MODE                        = ' '
    CONFIRM_OVERWRITE               = 'X' "Overwrite The File Only After
                    Confirmation                          
  NO_AUTH_CHECK                   = ' '
  CODEPAGE                        = ' '
  IGNORE_CERR                     = ABAP_TRUE
  REPLACEMENT                     = '#'
  WRITE_BOM                       = ' '
  TRUNC_TRAILING_BLANKS_EOL       = 'X'
  WK1_N_FORMAT                    = ' '
  WK1_N_SIZE                      = ' '
  WK1_T_FORMAT                    = ' '
  WK1_T_SIZE                      = ' '
  WRITE_LF_AFTER_LAST_LINE        = ABAP_TRUE
IMPORTING
  FILELENGTH                      =
  TABLES
    DATA_TAB                        = IT_VBAK
  FIELDNAMES                      =
EXCEPTIONS
  FILE_WRITE_ERROR                = 1
  NO_BATCH                        = 2
  GUI_REFUSE_FILETRANSFER         = 3
  INVALID_TYPE                    = 4
  NO_AUTHORITY                    = 5
  UNKNOWN_ERROR                   = 6
  HEADER_NOT_ALLOWED              = 7
  SEPARATOR_NOT_ALLOWED           = 8
  FILESIZE_NOT_ALLOWED            = 9
  HEADER_TOO_LONG                 = 10
  DP_ERROR_CREATE                 = 11
  DP_ERROR_SEND                   = 12
  DP_ERROR_WRITE                  = 13
  UNKNOWN_DP_ERROR                = 14
  ACCESS_DENIED                   = 15
  DP_OUT_OF_MEMORY                = 16
  DISK_FULL                       = 17
  DP_TIMEOUT                      = 18
  FILE_NOT_FOUND                  = 19
  DATAPROVIDER_EXCEPTION          = 20
  CONTROL_FLUSH_ERROR             = 21
  OTHERS                          = 22
IF SY-SUBRC <> 0.
MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
        WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
ENDIF.
if u need any more then i welcome u to clarify it.
reward points,if it is useful.

Similar Messages

  • Can't delete a .zip.download file on desktop

    I got this file while downloading files from my Outlook Web Access. The files were moved to a folder but this file remains on my desktop and doesn't allow me to trash it. Any help is appreciated.

    Open the Terminal in the Utilities folder. At the Terminal's prompt paste the following:
    sudo rm -rf ~/Desktop/
    Now drag the file icon into the Terminal window. Press RETURN. Enter your admin password when requested. It is not echoed to the screen. Press RETURN again.
    You can also see if it can be removed using Trash It! 5.1.
    If all else fails visit The XLab FAQs and read the FAQ on resolving Trash problems.

  • Missing download files on desktop

    Sometimes when I download files to the desktop they are missing.
    A lot of times, I will "print to a PDF" and save it to the desktop. Then it's missing???
    What can I do to fix?
    Kevin

    I found this in the Safari Help Menu:
    Finding files you download
    Files you download are copied to the download location specified in the General pane of Safari preferences.
    Safari is set up to download files to your Desktop folder, but you can select a different location. To see where files are downloaded, open the General pane of Safari preferences.
    To see a downloaded file in the Finder, click the magnifying glass next to the filename in the Downloads window, which appears when you download the file.
    If you don't see the Downloads window, choose Downloads from the Window menu.
    If you download a disk image file, Safari shows the name of the disk image volume in the Downloads window. If you have unmounted the volume when you click the magnifying glass, Safari shows the disk image file in the Finder.
    If you download an Internet Disk Image, Safari decompresses the file and copies its contents to the download location, then moves the disk image to the Trash. If you click the magnifying glass, you will see the contents of the download location. If you want to save the disk image file, you need to drag it out of the Trash.
    * With Safari open click Safari/Preferences from the Menu. Click the General tab. Where it says; Save Downloaded Files To, use the pop up menu to designate where you want the files to go.
    I see where you're talking about File/Pring/PDF. Just click the PDF button and a dialog box will appear. Make sure the pop up menu says Desktop if that is where you want to keep it.
    Carolyn

  • Downloading files on desktop.

    Hi, when I download a file on desktop it arranges it on top of another file. I have my documents and folders arranged by date created. Could this be a sign of a virus. It seems that if you download something on the desktop it should place itself in the arranged setting. I would appreciate your feedback. Thank you.

    If you have the files Arranged by Size, the Macintosh HD would be on top and items
    such as alias to folders in the hard drive or other location, lower on the pile; and the
    other kinds of items may be more mixed up; & you can choose to hide the Mac HD.
    My desktop has three folder aliases on it. Anything more than that, not in use or to be
    trashed soon, is only there temporarily. A folder on the hard disk drive (since I am a
    single user on my computer, ownership to me does not matter) I can put items there.
    Or in the user-account named folder, and drag item folder to the Dock near the Trash.
    In mine, I hide a Saved Alias Folder there to run stuff that is not in the Dock. Any alias
    including ones to additional folders, or printer controls otherwise hidden further in a
    different location can be aliased and put within 'single-click reach' of the Desktop. (The
    real 'saved alias folder' is in the Misc Extras folder on the hard disk drive.)
    The order of items on the desktop (Finder) can help to organize them; if you edit
    files on the desktop, it is good to have next to nothing else there, so you can drag
    the items in progress to other locations; not move them with others to wrong places.
    My computer has Misc Extras (folder) on hard disk drive, & an alias to it on the
    desktop; there are folders within it that I have created so I know where most of
    the stuff I am using is. Often I put it there manually, then I know the path to get it.
    If working with a digital camera and manually editing images outside of iPhoto,
    my image editor software can be used to automatically find the folders I made
    for each dated saved collection of images from the camera, so these are often
    saved to a folder in my Misc Extras by camera name, day/month/year. These
    get burned to DVD later, and eventually removed from the hard disk drive.
    There are several ways to use folders and aliases in pre-Stacks Leopard.
    {You can re-order items out of alphabetical order by adding a space in
    front of the first letter of the name of the item or alias. I use that to make
    accessing Disk Utility easier from GO in the Finder menu, it now is first.}
    Good luck & happy computing!
    { edited 2x }

  • Can't find downloaded files on desktop

    I can't find files that safari automatically downloaded to desktop, they don't show in my finder when I go to desktop.
    However, when changing the settings in Safari on where the files download to, I can see these files but can't access or delete them.
    What to do?

    Hi apeu,
    I had an Apple lle, lots of water under the bridge since then
    The Apple tutorial Mac 101 is very helpful.
    Also, at your bookstore for a more in-depth view, "Mac OS X Tiger, The Missing Manual" by David Pogue.
    -mj
    [email protected]

  • Cannot download files onto desktop

    I have a problem downloading attachments from my email onto my desktop. in the download window it always says "cannot create file". i am mainly trying to download pdf files. it was working last week but know not at all.
    David

    Welcome To Discussions David!
    Navigate to HD > Users > Your Account.
    Click once on Desktop to highlight.
    Press the Command + I keys to Get Info.
    In the window that opens, click the Disclosure Triangle for Ownership & Permissions.
    -What information is displayed:
    You can Here?
    Click the Disclosure Triamgle for Details.
    -What information is displayed:
    Owner: Here?
    Access: Here?
    ali b

  • How do I get rid of the downloaded files showing on my desktop?

    That is what do I have to do so that my downloads do not show up on the desktop whether they are simple documents or program files?  If I put them in the trash it seems to delete them altogether... Any advice will be very welcome as my desktop is almost full of downloaded file icons

    It's not good practice to have a desktop full of icons. Is that your default download location? If so, you'd do better to designate a new destination, maybe the Downloads folder on your user account. Or any folder you create.
    Each web browser will allow you to select a destination in its preferences.

  • Remote Desktop -  can't download file

    We have a server mac and we can access at server with remote desktop with a other mac, but we can't download file. Where is a problem? Is a port closed?

    I had access for download the files but not now, the configuration is not changing.

  • I just downloaded Autocad to my downloads file, how do I take it from there to my Parallels Desktop without using "Windows Explorer"?

    I just downloaded Autocad to my downloads file, how do I take it from there to my Parallels Desktop without using "Windows Explorer"?

    Did you download it from Adobe or a pop up? If it was a pop up do not open it. Make sure you only get it directly from Adobe here:
    http://get.adobe.com/flashplayer/
    There is some malware that poses as Flash, in pop ups.
    Then do as macbig explained double click on the file,
    After you open and install the .dmg reboot your computer to complete the installation

  • How can I make sure that a downloaded file goes to the left of the desktop

    Hi all,
    This may be a stupid question but I havent found the answer after much searching. Basically I like to have my dock on the right. And because of that, I life to have all the icons on my dekstop on the left. No problem so far. I managed to move the HD icons by making aliases and unticking the keep arranged option. So now all my desktop icons are on the left exactly where I want them to be. However when I download a file, that file shows up on the right of the desktop! I would really like it to just fall in line with the other icons, i.e. on the left.
    You may think im being picky but the thing is, I download a lot of files, and what ends up happening is I get a column of files on the right, very close to the dock (so close in fact that their names are hidden by it). So it is quite annoying.
    I would appreciate any help.

    Hi kakeez,
    If I were you, I'd create a folder named "Recent Downloads", place it on the left on my desktop, and set my browser's preferences to
    "*Save downloaded files to:*" this folder.
    Note that you can also play with the Finder's View Options (command+J) so that size of the icons combined with label position (bottom or right) make it look good and handy with the dock on the right.
    That's what I do myself. I use icon size 40 and text size 11pt, with the label on the right.
    With the "Snap to Grid" option checked, it all fits beautifully with my Dock on the right of my screen.
    Tip:
    One of the known factors of slowing down Mac OS X, is to have a lot of icons (no matter which) on the desktop.
    So if you don't care about a beautiful wallpaper, free of cluttering icons all over it,
    at least consider this slowing down aspect:
    ~ it is much better to create folders within the Documents, Pictures, Movies folders, or also at the top level of Macintosh HD or each User's,
    and organize your work that way, so you can keep as few icons as possible on the Desktop.
    Axel

  • Why does FF save files to desktop, when I have "downloads" checked in options? This is a new issue with the latest version 3.6.3 Windows XP Thanks.

    Why does FF save files to desktop, when I have "downloads" checked in options? This is a new issue with the latest version 3.6.3 . Using Windows XP Driving me nuttier! Thanks.
    (Is is that MicroNetFrame Asst thing?)
    == This happened ==
    Every time Firefox opened
    == When I installed latest version

    Thanks for your reply. I appreciate your help.
    It was just a hunch that MircoNetFrame was causing the problem. I disabled it as you suggested, and I still have the problem.
    I just changed under Tools>Options> General - had checked "ask me every time" under downloads, so instead of asking me, FF saved the download to I know not where. It no longer saves it to the desktop, leaving a duplicate in "my documents".
    In windows, I have found unless one knows the entire name of the document, one can never find anything. It isn't listed under recent ''''''__. I can't recall the nomenclature, but the
    capability is ridiculous. So, I don't know where that file I just downloaded is!
    I downloaded a PDF file, but this happens with all DL's. It was so easy to have them all stacked in one place and I could recall
    what I had and when I downloaded it easily.
    Do you have any other suggestions other that going back to the old version of FF, which I would rather not do?
    Thanks again for your time, it is very considerate to help a complete stranger, I must say. Sounds like something I might do! Cheers!

  • Firefox crashes when uploading/downloading files from/to 'desktop folder'

    Hello
    I'm hoping, that you can help me!
    I'm using Firefox 28.0 on MacBook Pro Mavericks 10.9.2
    Firefox crashes/freezes when I try to upload/download files from/to my 'desktop folder'.
    I't only happens, when I use this folder. Download to 'download folder' or any other folder works fine.
    Download to 'desktop folder' when using Safari also works fine.
    I't only happens when desktop and firefox tries to communicate.
    It's very annoying when I accidentally forget, that the bugs is there, and I have to force quit and start all over again. And sometimes I don't even have a choice, because 'desktop' randomly opens as default folder, when I try to upload things.
    Thank you so much in advance!
    Kind regards Elizabeth

    Hi ESwan,
    I am not a Mac user so not the best person to attempt to assist but here goes.
    I am presuming that info such as
    PID: 1695 Event: cpu usage (microstackshots only)
    Relate to the Mac OS X crash & event logging and reporting.
    What we need are the ones that Firefox itself generates and submits for processing by Mozilla Firefox
    * See [[Firefox crashes - Troubleshoot, prevent and get help fixing crashes#w_get-help-fixing-this-crash]]'''#w_get-help-fixing-this-crash'''
    From what you say the crashes occur after a certain action and I am hoping that you will be able to use the easy method as in the article linked above. Navigate to about:crashes by keying ''about:crashes'' into the address bar. You are loolking for the ones starting wth ''bp-'' Paste two or three of those into your next post. Include the bp- part but not any link information before that. After they are pasted into the forum the forum software changed them to be links.

  • Downloaded files don't appear on desktop

    I just started experiencing an odd problem and when I went searching, I found the topic in the archives, unanswered - so I thought I would try again.
    For the last few days, everything I download to the desktop - doesn't appear on my desktop. When I search in my downloads folder, I find all of the files, but they don't physically show up unless I relaunch the finder - which is frustrating and annoying.
    Does anyone know what causes this? The posts relating to this problem go back quite a way, so it can't be an update issue and I haven't changed any settings or loaded any new software recently.
    Any thoughts?

    Thanks for clarifying. Are you saying that there's a folder named downloads on your Desktop that you're not seeing getting filled with the downloads or is the Desktop your downloads folder? In any case, you're describing a Finder hangup that's been around for quite awhile, but yours is extremely rare in that only relaunching the Finder gets it to update properly. Create a new admin user account, log into it, set up your browser to download to the Desktop, download some things, and see if the problem persists. Report back.

  • I would click on the file it will download to my desktop I need help

    I have a table in one of the column I would like to able download a file to the my desktop. SQL code
    EX: I would click on the file it will download to my desktop.

    I have a table in one of the column
    I would click on the file it will download to my desktop.
    Not sure what you want to do. Can you explain it better?

  • ALL DOWNLOADS DISTORT ALL FILES AND DESKTOP

    WINDOWS XP PRO 32. internet explorer 8. I HAVE INSTALLED AND UNINSTALLED READER AND FLASH PLAYER SEVERAL TIMES, WITH SAME RESULTS, WITH AND WITHOUT GOOGLE CHROME SELECTED.
    ALL Files and desktop  are so large they can not be navigated.

    A screen shot might be better, but try this anyway.
    If you haven't already rebooted, do so.
    Right click an empty bit of the desktop.
    Choose Properties
    Click Appearance
    Look under Font Size: make sure it is NORMAL.

Maybe you are looking for

  • Multiple Alerts getting raised for same Error

    Hi All, I have a Management Pack Which will will trigger an Exe. The Exe takes an input and that input is being provided as a parameter from the MP. Whenever the exe raises throws an error an event in the event viewer and also  we are raising an Aler

  • Storing data in database

    create a table called "details" in MS SQL.create a DSN named userdsn that connects to the details table create an app that has 5 text fields and a submit button . when the user clicks on the submit button, a connection should be made to a DSN named "

  • Numbers not synching across devices

    I continue to run into a synch problem with Numbers.  I have a spreadsheet that I update regularly, but when I open it, it regularly shows more than one spreadsheet and says they are out of synchronization and I need to pick one.  the latest message

  • I am new to alv grid

    Can u tell me which document i have to refer so that in a short time i can know abt alv grid and can start my project work

  • Upload maveric Imovie/now what MY Iphoto IMAGES? its a mess!

      I did not finnishUpdating downloading imovie,,and now...  I DID and am given a chose ??or what of what to keep? MY MOVIES ARE GONE" as also I see 2 versions of iphoto Blacked up and TO ' choose what! I do not understand I believe I might press wron