Who is patient it is difficult

well i have this program ( about 3000 rows) when i execute it , it is displayed the balance carry forward for each vendor and customer. this is my problem. i want it to be displayed right down of the header the whole balance carry forward for all customers and vendors ( not for each vendor-customer) . i will reward with points for helpful answers. pls it's urgent. here is the code:
*&   Written by: Antonis Nezos
REPORT  z_1gvcl000_v1  NO STANDARD PAGE HEADING
                    MESSAGE-ID 00
                    LINE-COUNT 58(3).
- Global declarations -
TABLES : kna1, knb1, knc1, bsid, bsad, bkpf, t001, t001a, t000,
         t005, t880, t004, ska1, skb1, tbslt, bsec, j_2gmd, tcurt.
TABLES : lfa1, lfb1, lfc1, bsik, bsak.
INCLUDE j_1gspledger.
<< AN
DATA: BEGIN OF ilifnr OCCURS 0,
      lifnr LIKE lfa1-lifnr,
      kunnr LIKE lfa1-kunnr.
DATA: END OF ilifnr.
RANGES:r_kunnr FOR lfa1-kunnr.
DATA:w_lines TYPE p DECIMALS 0.
>> AN
FIELD GROUPS ***
FIELD-GROUPS : header, daten.
DATA :
  BEGIN OF f_group,
    bukrs LIKE lfb1-bukrs,
    lifnr LIKE lfa1-lifnr,
    kunnr LIKE kna1-kunnr,
    akont LIKE lfb1-akont,
    umskz LIKE bsik-umskz,
    id(1),  " 1 = Previous year 2 = Previous dates 3 = Current dates
    otcname LIKE bsec-name1,     " One time vendor name
    budat LIKE bsik-budat,
    xblnr LIKE bsik-xblnr,
    belnr LIKE bsik-belnr,
    buzei LIKE bsik-buzei,
    blart LIKE bsik-blart,
    bschl LIKE bsik-bschl,
    bldat LIKE bsik-bldat,
    waers LIKE bsik-waers,       " Transaction currency
    sgtxt LIKE bsik-sgtxt,
    debitt LIKE bseg-wrbtr,      " In transaction currency
    creditt LIKE bseg-wrbtr,
    balancet LIKE bseg-wrbtr,
    debitl LIKE  bseg-dmbtr,     " In local currency
    creditl LIKE bseg-dmbtr,
    balancel LIKE bseg-dmbtr,
  END OF f_group.
INSERT f_group-bukrs f_group-lifnr f_group-kunnr f_group-akont "SPOT
            f_group-umskz
       f_group-id  f_group-otcname f_group-budat f_group-belnr
       f_group-buzei
       INTO header.
INSERT f_group-blart f_group-bschl f_group-xblnr
       f_group-bldat f_group-waers f_group-sgtxt
       f_group-debitt f_group-creditt f_group-balancet
       f_group-debitl f_group-creditl f_group-balancel
       INTO daten.
DATA DECLARATIONS ***
DATA : success.
DATA : method(1) TYPE n.       " Read standard or extended ledger
DATA : msgtab LIKE fimsg OCCURS 100 WITH HEADER LINE.
DATA : no_headers.
DATA : g_curr LIKE bsik-waers.
DATA : g_curr_t LIKE tcurt-ktext.
DATA : wrote_previous_year.
DATA : wrote_previous_dates.
DATA : g_header(255).
DATA : g_len TYPE i.
DATA : date_string(100).
DATA : h_bukrs LIKE bsik-bukrs.
DATA : h_belnr LIKE bsik-belnr.
DATA : h_gjahr LIKE bsik-gjahr.
DATA : h_akont LIKE bsik-hkont.
DATA : h_lifnr LIKE bsik-lifnr.
DATA : h_kunnr LIKE bsid-kunnr.   "SPOT
RANGES : valid_accounts FOR bsis-hkont.
RANGES : r_umskz FOR bsik-umskz.
Internal table with companies and chart of account used
DATA : BEGIN OF charts_tab OCCURS 10,
         bukrs LIKE t001-bukrs,
         chart LIKE t001-ktopl,
         sakln LIKE t004-sakln,
       END OF charts_tab.
Currencies tables
DATA : BEGIN OF currency_tab OCCURS 100,
         bukrs LIKE t001-bukrs,
         waers LIKE t001-waers,
         curtp LIKE t001-waers,        " Type of currency
       END OF currency_tab.
Ranges and variables that dictate time periods to read.
DATA   : last_previous_period LIKE bkpf-monat. " last previous period.
RANGES : previous_dates FOR sy-datum.
RANGES : all_dates FOR sy-datum.
Summation tables
DATA : BEGIN OF sum_bukrs,             " Summation on local currency
         debitl LIKE lfc1-umsav,
         creditl LIKE lfc1-umsav,
         balancel LIKE lfc1-umsav,
       END OF sum_bukrs.
DATA : BEGIN OF sum_bukrs_t OCCURS 5,  " Summations on transaction curr
         waers LIKE bsik-waers,
         debitt LIKE lfc1-umsav,
         creditt LIKE lfc1-umsav,
         balancet LIKE lfc1-umsav,
       END OF sum_bukrs_t.
DATA : sum_umskz LIKE sum_bukrs.
DATA : sum_umskz_t LIKE sum_bukrs_t OCCURS 5 WITH HEADER LINE.
For previous years
DATA : sum_umskz_py LIKE sum_bukrs.
DATA : sum_umskz_t_py LIKE sum_bukrs_t OCCURS 5 WITH HEADER LINE.
For previous dates
DATA : sum_umskz_pd LIKE sum_bukrs.
DATA : sum_umskz_t_pd LIKE sum_bukrs_t OCCURS 5 WITH HEADER LINE.
Vendor totals
DATA : sum_lifnr LIKE sum_bukrs.
DATA : sum_lifnr_t LIKE sum_bukrs_t OCCURS 5 WITH HEADER LINE.
Customer totals
DATA : sum_kunnr LIKE sum_bukrs.
DATA : sum_kunnr_t LIKE sum_bukrs_t OCCURS 5 WITH HEADER LINE.
For page and carry forward totals.
DATA : sum_page LIKE sum_bukrs.
DATA : sum_cfw LIKE sum_bukrs.
Summation structures ON XBLNR ( reference document )
DATA : items LIKE f_group OCCURS 100 WITH HEADER LINE.
DATA : BEGIN OF xblnr_sum OCCURS 10,
         xblnr LIKE bsik-xblnr,
         budat LIKE bsik-budat,
         bschl LIKE bsik-bschl,
         waers LIKE bsik-waers,        " Currency of transaction
         debitl LIKE  lfc1-umsav,
         creditl LIKE lfc1-umsav,
         balancel LIKE lfc1-umsav,
         debitt LIKE  lfc1-umsav,
         creditt LIKE lfc1-umsav,
         balancet LIKE lfc1-umsav,
         counter TYPE i,               " How many collects where done
       END OF xblnr_sum.
OUTPUT STRUCTURES ***
DATA : BEGIN OF out_1,                 " General info
          budat(10),
          v1(1),
          bldat(10),                       "gleventis 12.07.2006
          v5(1),                           "gleventis 12.07.2006
          xblnr LIKE bsik-xblnr,
          v2(1),
          belnr LIKE bsik-belnr,
          v3(1),
          sgtxt(50),
          v4(1),
          bschl LIKE bsik-bschl,
       END OF out_1,
       BEGIN OF out_2,                 " Local currency
          v1(1),
          debitl(16),
          v2(1),
          creditl(16),
          v3(1),
          balancel(17),
       END OF out_2,
       BEGIN OF out_3,                 " Transaction currency
          v1(1),
          debitt(16),
          v2(1),
          creditt(16),
          v3(1),
          balancet(17),
          v4(1),
          waers(4),
       END OF out_3.
DATA : cfw_1 LIKE out_1.               " For carry forwards
DATA : cfw_2 LIKE out_2.
DATA : pg_1 LIKE out_1.                " For page totals
DATA : pg_2 LIKE out_2.
DATA : bukrs_page LIKE sy-pagno.
- Selection screen definitions -
PARAMETERS: s_ledger LIKE t881-rldnr DEFAULT 'ZD'.
SELECT-OPTIONS: s_bukrs FOR lfb1-bukrs MEMORY ID buk.
SELECT-OPTIONS s_lifnr FOR lfb1-lifnr MATCHCODE OBJECT kred.
SELECTION-SCREEN ULINE.
SELECT-OPTIONS: s_akont FOR lfb1-akont.        " Reconciliation accounts
In which chart of accounts the results will be displayed
SELECTION-SCREEN COMMENT /1(60) text-004.
PARAMETERS s_chart RADIOBUTTON GROUP y." Chart of accounts of company
PARAMETERS s_altk RADIOBUTTON GROUP y. " Alternative chart of accounts
PARAMETERS s_group RADIOBUTTON GROUP y." Group chart of accounts
In which chart of accounts the range of reconciliation accounts
where given by the user
SELECTION-SCREEN COMMENT /1(60) text-019.
PARAMETERS s_acch RADIOBUTTON GROUP j.
PARAMETERS s_asch RADIOBUTTON GROUP j DEFAULT 'X'.
Use 2nd parallel currency
PARAMETERS : s_2curr AS CHECKBOX.
SELECTION-SCREEN ULINE.
Selections on special G/Ls
SELECTION-SCREEN BEGIN OF LINE.
PARAMETERS :  s_umskzn RADIOBUTTON GROUP c DEFAULT 'X'. " Normal G/Ls
SELECTION-SCREEN COMMENT (30) text-001.
PARAMETERS :  s_umskzs RADIOBUTTON GROUP c.             " Special G/Ls
SELECTION-SCREEN COMMENT (30) text-002.
PARAMETERS :  s_umskzb RADIOBUTTON GROUP c.             " Both
SELECTION-SCREEN COMMENT (30) text-003.
SELECTION-SCREEN END OF LINE.
Range of special g/L transactions
SELECT-OPTIONS : s_umskz FOR bsik-umskz.
SELECTION-SCREEN ULINE.
Posting dates
PARAMETERS:
  s_gjahr LIKE bkpf-gjahr OBLIGATORY DEFAULT sy-datum(4).
SELECT-OPTIONS:
  s_budat FOR bkpf-budat OBLIGATORY NO-EXTENSION DEFAULT sy-datum.
SELECTION-SCREEN ULINE.
Read previous year balance
PARAMETERS : s_rprevy AS CHECKBOX DEFAULT 'X'.
Read previous dates
PARAMETERS : s_rprevd AS CHECKBOX DEFAULT 'X'.
Print vendors not posted to.
PARAMETERS : s_nonpos AS CHECKBOX.
The following vendors not posted to
SELECT-OPTIONS : s_cusnon FOR lfb1-lifnr MATCHCODE OBJECT kred.
Print one time vendor data.
PARAMETERS : s_onetim AS CHECKBOX.
Amounts in transaction currency
PARAMETERS : s_tran AS CHECKBOX.
Sums on XBLNR
PARAMETERS : s_sxblnr AS CHECKBOX.
Show same XBLNRS as one line
PARAMETERS : s_xblnr AS CHECKBOX.
*<<< DDS Exclude documents with doc type 'CL'
PARAMETERS : s_cl AS CHECKBOX.
*>>> DDS
SELECTION-SCREEN ULINE.
Print user selections.
PARAMETERS : s_psel AS CHECKBOX.
- Selection screen processing -
{ au1++
**********************************************TEST temp
AT SELECTION-SCREEN ON s_bukrs.
  call function 'J_1GBUKRS_AUTH_CHECK'
    exporting
      i_xdb     = 'KB'
    tables
      it_buksel = s_bukrs.
AT SELECTION-SCREEN.
  AUTHORITY-CHECK OBJECT 'F_BKPF_KOA'
                  ID 'KOART' FIELD 'K'
                  ID 'ACTVT' FIELD '03'.
  IF sy-subrc <> 0.
    MESSAGE e482(f4).
  ENDIF.
} au1
AT SELECTION-SCREEN ON VALUE-REQUEST FOR s_akont-low.
  CALL FUNCTION 'FI_F4_AKONT'
    EXPORTING
      i_bukrs        = s_bukrs-low
      i_mitkz        = 'K'
    IMPORTING
      e_akont        = s_akont-low
    EXCEPTIONS
      invalid_call   = 1
      nothing_found  = 2
      internal_error = 3
      OTHERS         = 4.
AT SELECTION-SCREEN ON VALUE-REQUEST FOR s_akont-high.
  CALL FUNCTION 'FI_F4_AKONT'
    EXPORTING
      i_bukrs        = s_bukrs-low
      i_mitkz        = 'K'
    IMPORTING
      e_akont        = s_akont-high
    EXCEPTIONS
      invalid_call   = 1
      nothing_found  = 2
      internal_error = 3
      OTHERS         = 4.
- Data Selection part -
START-OF-SELECTION.
<< AN
  r_kunnr-sign   = 'I'.
  r_kunnr-option = 'EQ'.
  SELECT * FROM lfa1 WHERE lifnr IN s_lifnr.
    IF NOT lfa1-kunnr IS INITIAL.
      ilifnr-kunnr = lfa1-kunnr.
      ilifnr-lifnr = lfa1-lifnr.
      APPEND ilifnr.
      CLEAR: ilifnr.
      r_kunnr-low = lfa1-kunnr.
      COLLECT r_kunnr.
    ENDIF.
  ENDSELECT.
*>> AN
  CALL FUNCTION 'FI_MESSAGE_INIT'.
  PERFORM create_headers.
  PERFORM setup_glind.
get spl summary table
  IF NOT s_ledger IS INITIAL.
    PERFORM get_ledger_table USING s_ledger
                          CHANGING table.
    IF table IS INITIAL.
      MESSAGE s000(8n1) WITH text-s01 s_ledger.
      LEAVE PROGRAM.
    ENDIF.
  compare spl summary table with program data type
    PERFORM check_summary_table CHANGING l_table_differs.
    IF l_table_differs = c_true.
      IF sy-batch <> 'X'.              " (Running in dialog mode)
        string = text-s02.
        REPLACE '$' WITH table INTO string.
        CONDENSE string.
        CALL FUNCTION 'POPUP_TO_DISPLAY_TEXT'
          EXPORTING
            titel     = sy-title
            textline1 = string
            textline2 = text-s03.
      ENDIF.
    ENDIF.
  ENDIF.                               " not s_ledger is initial
  SELECT * FROM t001 WHERE bukrs IN s_bukrs.
    PERFORM check_posting USING t001 success.
    CHECK success = 'X'.
    PERFORM setup_periods USING  t001-bukrs s_gjahr success.
    CHECK success = 'X'.
    PERFORM setup_currency USING t001 success.
    CHECK success = 'X'.
    PERFORM set_up_chart USING t001 success.
    CHECK success = 'X'.
    PERFORM setup_accounts USING t001. " Setup valid accounts
    IF s_rprevy = 'X' OR s_rprevd = 'X'.
      PERFORM determine_method USING t001.
     << AN
      method = 2.
     >> AN
      IF method = 1.                   " Read from standard ledger "SPOT
        PERFORM collect_knc1 USING t001-bukrs.
        PERFORM collect_lfc1 USING t001-bukrs.
      ELSE.                            " Read from special ledger
        PERFORM collect_extended USING t001-bukrs success.
        CHECK success = 'X'.
      ENDIF.
    ENDIF.
    PERFORM collect_transactions USING t001-bukrs 'BSIK'.
    PERFORM collect_transactions USING t001-bukrs 'BSAK'.
    PERFORM collect_transactions_bsid USING t001-bukrs 'BSID'.
    PERFORM collect_transactions_bsid USING t001-bukrs 'BSAD'.
    IF s_nonpos = 'X' AND ( s_umskzn = 'X' OR s_umskzb = 'X' ).
      PERFORM create_dummy_entries USING t001.
    ENDIF.
  ENDSELECT.
- Processing part -
END-OF-SELECTION.
  IF s_tran = ' '.
    NEW-PAGE LINE-SIZE 170.
  ELSE.
    NEW-PAGE LINE-SIZE 255.
  ENDIF.
  PERFORM set_headers(sapfj1glbh)
      USING '' '' '' '' '' '' '' '' '*' 'X'.
  SORT.
  LOOP.
    AT NEW f_group-bukrs.
      CLEAR bukrs_page.                " Page counter for company
      PERFORM create_bukrs_info.
      CLEAR sum_cfw.
      CLEAR : sum_bukrs, sum_bukrs_t[], sum_bukrs_t.
      READ TABLE currency_tab WITH KEY bukrs = f_group-bukrs.
      g_curr = currency_tab-waers.
      CLEAR tcurt.
      SELECT SINGLE * FROM tcurt WHERE spras = sy-langu AND
                                       waers = g_curr.
      g_curr_t = tcurt-ktext.
      NEW-PAGE.
    ENDAT.
    AT NEW f_group-lifnr.
      PERFORM write_lifnr.
      CLEAR : sum_lifnr, sum_lifnr_t[], sum_lifnr_t.
    ENDAT.
    AT NEW f_group-kunnr.
      PERFORM write_kunnr.
      CLEAR : sum_kunnr, sum_kunnr_t[], sum_kunnr_t.
    ENDAT.
    AT NEW f_group-umskz.
      PERFORM write_umskz.
      CLEAR : sum_umskz, sum_umskz_t[], sum_umskz_t.
      CLEAR : sum_umskz_py, sum_umskz_t_py[], sum_umskz_t_py.
      CLEAR : sum_umskz_pd, sum_umskz_t_pd[], sum_umskz_t_pd.
      CLEAR : wrote_previous_year, wrote_previous_dates.
    ENDAT.
    AT NEW f_group-otcname.
      IF f_group-id = '3'.             " Line items
        IF f_group-otcname NE space.
          PERFORM write_one_time_vendor USING f_group.
          PERFORM write_one_time_customer USING f_group.
        ENDIF.
        CLEAR : items[], items, xblnr_sum[], xblnr_sum.
      ENDIF.
    ENDAT.
    IF ( f_group-id = '1' ).
      ADD-CORRESPONDING f_group TO sum_umskz_py.
      MOVE-CORRESPONDING f_group TO sum_umskz_t_py.
      COLLECT sum_umskz_t_py.
    ELSEIF ( f_group-id = '2' ).
      ADD-CORRESPONDING f_group TO sum_umskz_pd.
      MOVE-CORRESPONDING f_group TO sum_umskz_t_pd.
      COLLECT sum_umskz_t_pd.
    ELSE.                              " Line items
      IF s_sxblnr = 'X'.               " Sums on XBLNR
        MOVE-CORRESPONDING f_group TO items.
        APPEND items.
        MOVE-CORRESPONDING f_group TO xblnr_sum.
        IF s_tran NE 'X'.       " No transaction currency necessary
          CLEAR xblnr_sum-waers.
        ENDIF.
        xblnr_sum-counter = 1.
        COLLECT xblnr_sum.
      ELSE.
        ADD-CORRESPONDING f_group TO sum_umskz.
        MOVE-CORRESPONDING f_group TO sum_umskz_t.
        COLLECT sum_umskz_t.
        PERFORM write_line USING f_group.
      ENDIF.
    ENDIF.
    AT END OF f_group-otcname.
      IF f_group-id = '3'.
        IF s_sxblnr = 'X'.             " Sums on XBLNR
          PERFORM process_xblnr.
        ENDIF.
      ENDIF.
    ENDAT.
    AT END OF f_group-id.
      IF ( f_group-id = '1' ).
        ADD-CORRESPONDING sum_umskz_py TO sum_umskz.
        PERFORM pass_trans TABLES sum_umskz_t_py sum_umskz_t.
        PERFORM write_previous TABLES sum_umskz_t_py
                               USING sum_umskz_py '1'.
      ELSEIF ( f_group-id = '2' ).
        ADD-CORRESPONDING sum_umskz_pd TO sum_umskz.
        PERFORM pass_trans TABLES sum_umskz_t_pd sum_umskz_t.
        PERFORM write_previous TABLES sum_umskz_t_pd
                               USING sum_umskz_pd  '2'.
      ENDIF.
    ENDAT.
    AT END OF f_group-umskz.
      PERFORM write_end_account.
      ADD-CORRESPONDING sum_umskz TO sum_bukrs.
      PERFORM pass_trans TABLES sum_umskz_t sum_bukrs_t.
    ENDAT.
    AT END OF f_group-akont.
    ENDAT.
    AT END OF f_group-lifnr.
    ENDAT.
    AT END OF f_group-kunnr.
    ENDAT.
    AT END OF f_group-bukrs.
      PERFORM print_company_totals.
    ENDAT.
  ENDLOOP.
  PERFORM write_errors.
  IF s_psel = 'X'.
    PERFORM print_user_selections.
  ENDIF.
  CLEAR : h_bukrs, h_lifnr, h_kunnr, h_gjahr, h_akont, h_belnr.
TOP OF PAGE PROCESSING ***
TOP-OF-PAGE.
  CLEAR sum_page.
  ADD 1 TO bukrs_page.
  IF no_headers = space.
Create the header lines
    PERFORM write_headers(sapfj1glbh)
            USING t001
                  text-p01 ''
                  bukrs_page
                  date_string
                  g_curr
                  g_header ' '.
    ULINE.
Write carry forwards.
    IF bukrs_page NE 1.
      CLEAR : cfw_1, cfw_2.
      cfw_1-sgtxt = text-205.
      WRITE sum_cfw-debitl TO cfw_2-debitl CURRENCY g_curr.
      WRITE sum_cfw-creditl TO cfw_2-creditl CURRENCY g_curr.
      WRITE sum_cfw-balancel TO cfw_2-balancel CURRENCY g_curr.
      WRITE : / cfw_1 NO-GAP, cfw_2 NO-GAP.
    ENDIF.
    SKIP 1.
  ENDIF.
END OF PAGE PROCESSING ***
END-OF-PAGE.
  IF no_headers = space.
    SKIP 1.
Write page totals
    CLEAR : pg_1, pg_2.
    pg_1-sgtxt = text-203.
    WRITE sum_page-debitl TO pg_2-debitl CURRENCY g_curr.
    WRITE sum_page-creditl TO pg_2-creditl CURRENCY g_curr.
    WRITE sum_page-balancel TO pg_2-balancel CURRENCY g_curr.
    WRITE : / pg_1 NO-GAP, pg_2 NO-GAP.
Write carry forwards
    CLEAR : cfw_1, cfw_2.
    cfw_1-sgtxt = text-206.
    WRITE sum_cfw-debitl TO cfw_2-debitl CURRENCY g_curr.
    WRITE sum_cfw-creditl TO cfw_2-creditl CURRENCY g_curr.
    WRITE sum_cfw-balancel TO cfw_2-balancel CURRENCY g_curr.
    WRITE : / cfw_1 NO-GAP, cfw_2 NO-GAP.
  ENDIF.
- User Interaction part -
AT LINE-SELECTION.
  IF h_belnr NE space AND h_belnr NE '**********'.
    SET PARAMETER ID 'BLN' FIELD h_belnr.
    SET PARAMETER ID 'BUK' FIELD h_bukrs.
    SET PARAMETER ID 'GJR' FIELD h_gjahr.
    CALL TRANSACTION 'FB03' AND SKIP FIRST SCREEN.
  ELSEIF h_akont NE space.
    IF s_chart = 'X'.
      SET PARAMETER ID 'SAK' FIELD h_akont.
      SET PARAMETER ID 'BUK' FIELD h_bukrs.
      SET PARAMETER ID 'GJR' FIELD h_gjahr.
      CALL TRANSACTION 'FS10N' AND SKIP FIRST SCREEN.
    ENDIF.
  ELSEIF h_lifnr NE space.
    SET PARAMETER ID 'LIF' FIELD h_lifnr.
    SET PARAMETER ID 'BUK' FIELD h_bukrs.
    SET PARAMETER ID 'GJR' FIELD h_gjahr.
    CALL TRANSACTION 'FK10N' AND SKIP FIRST SCREEN.
  ELSEIF h_kunnr NE space.   "SPOT
    SET PARAMETER ID 'KUN' FIELD h_kunnr.
    SET PARAMETER ID 'BUK' FIELD h_bukrs.
    SET PARAMETER ID 'GJR' FIELD h_gjahr.
    CALL TRANSACTION 'FD10N' AND SKIP FIRST SCREEN.
  ENDIF.
  CLEAR : h_bukrs, h_lifnr,  h_kunnr, h_gjahr, h_akont, h_belnr.
- S u b r o u t i n e s -
  Determine if we should read from General Ledger or Special         *
  Further criteria in the selection screen should be tested here,    *
  if they create the necessity to read form an extended ledger       *
  It is advisable if an extended ledger exists to set up method      *
  always to 2 ( always to read from extended ledger )                *
  --- Read program documentation ---                                 *
FORM determine_method USING value(v_t001) STRUCTURE t001.
  READ TABLE currency_tab WITH KEY bukrs = v_t001-bukrs.
  IF ( s_umskzn EQ 'X' ) AND
     ( currency_tab-curtp = '10' ) AND
     ( s_tran NE 'X' ).
    method = 1.             " No need to read from special ledger
  ELSE.
    method = 2.             " Need to read from special ledger
  ENDIF.
  IF NOT s_ledger IS INITIAL.
    method = 2.
  ENDIF.
ENDFORM.                    "determine_method
  Set up the last previous period and the current periods.           *
FORM setup_periods USING value(pbukrs)
                          value(pgjahr)
                          success.
  DATA : period_l  LIKE   t009b-poper.
  DATA : BEGIN OF the_periods OCCURS 20.
          INCLUDE STRUCTURE periods.
  DATA : END OF the_periods.
  DATA : date_low LIKE sy-datum.
  DATA : date_high LIKE sy-datum.
  DATA : w_date LIKE sy-datum.
  DATA : 1st_date LIKE sy-datum.
  DATA : t001_wa LIKE t001.
  success = 'X'.
Clear all date structures
  CLEAR last_previous_period.
  CLEAR previous_dates.      REFRESH previous_dates.
  CLEAR all_dates.           REFRESH all_dates.
Put selected dates into all_dates.
  LOOP AT s_budat.
    MOVE s_budat TO all_dates.
    APPEND all_dates.
  ENDLOOP.
No need to read periods balance
  IF s_rprevy = space AND s_rprevd = space.
    EXIT.
  ENDIF.
  SELECT SINGLE * FROM t001 INTO t001_wa WHERE bukrs = pbukrs.
  CALL FUNCTION 'G_PERIODS_OF_YEAR_GET'
    EXPORTING
      variant             = t001_wa-periv
      year                = pgjahr
    IMPORTING
      last_normal_period  = period_l
    TABLES
      i_periods           = the_periods
    EXCEPTIONS
      variant_not_defined = 1
      year_not_defined    = 2
      OTHERS              = 3.
  IF sy-subrc NE 0.
    CLEAR msgtab.
    msgtab-msort = '5'.
    msgtab-msgid = '00'.
    msgtab-msgty = 'E'.
    msgtab-msgno = '398'.
    msgtab-msgv1 = pbukrs.
    CALL FUNCTION 'FI_MESSAGE_COLLECT'
      EXPORTING
        i_fimsg = msgtab.
    CLEAR success.
    EXIT.
  ENDIF.
  READ TABLE s_budat INDEX 1.
  date_low = s_budat-low.
  IF s_budat-high NE 0.
    date_high = s_budat-high.
  ELSE.
    date_high = s_budat-low.
  ENDIF.
  SORT the_periods  BY buper.
  LOOP AT the_periods.
    IF date_low > the_periods-datbi.
      last_previous_period = the_periods-buper.
    ENDIF.
  ENDLOOP.
Set up dates
  LOOP AT the_periods.
    IF date_low BETWEEN the_periods-datab AND
                        the_periods-datbi.
      IF date_low GT the_periods-datab.
        CLEAR previous_dates.
        previous_dates-sign = 'I'.
        previous_dates-option = 'BT'.
        previous_dates-low = the_periods-datab.
        previous_dates-high = date_low - 1.
        APPEND previous_dates.
        MOVE previous_dates TO all_dates.
        APPEND all_dates.
      ENDIF.
      EXIT.
    ENDIF.
  ENDLOOP.
ENDFORM.                    "setup_periods
Write errors that occured                                            *
FORM write_errors.
  DATA xfeld.
  no_headers ='X'.
  CALL FUNCTION 'FI_MESSAGE_CHECK'
    EXCEPTIONS
      no_message = 01.
  IF sy-subrc = 0.
    NEW-PAGE.
    ULINE.
    WRITE text-f00.
    ULINE.
    CALL FUNCTION 'FI_MESSAGE_SORT'.
    CLEAR   msgtab.
    REFRESH msgtab.
    CALL FUNCTION 'FI_MESSAGE_GET_MSORT'
      IMPORTING
        e_xinit    = xfeld
      TABLES
        s_fimsg    = msgtab
      EXCEPTIONS
        no_message = 1.
    IF sy-subrc = 0.
      LOOP AT msgtab.
        CASE msgtab-msort.
          WHEN '1'.
            WRITE text-f01 COLOR 3.
          WHEN '2'.
            WRITE text-f02 COLOR 3.
          WHEN '3'.
            WRITE text-f03 COLOR 3.
          WHEN '4'.
            WRITE text-f04 COLOR 3.
          WHEN '5'.
            WRITE text-f05 COLOR 3.
          WHEN '6'.
            WRITE text-f06 COLOR 3.
          WHEN '7'.
            WRITE text-f07 COLOR 3.
          WHEN '8'.
            WRITE text-f08 COLOR 3.
          WHEN '9'.
            WRITE text-f09 COLOR 3.
        ENDCASE.
        CALL FUNCTION 'FI_MESSAGE_PRINT'
          EXPORTING
            i_msort = msgtab-msort
            i_xausn = ' '
            i_xeaus = 'X'
            i_xskip = ' '.
        SKIP.
      ENDLOOP.
    ENDIF.
  ENDIF.
ENDFORM.                    "write_errors
  Setup currencies
FORM setup_currency USING
                         value(v_t001) STRUCTURE t001
                         p_success.
  PERFORM test_currency USING v_t001 p_success.
  CHECK p_success = space.             " Currency determination failed
  CLEAR msgtab.
  msgtab-msort = '2'.
  msgtab-msgid = '00'.
  msgtab-msgty = 'E'.
  msgtab-msgno = '398'.
  msgtab-msgv1 = v_t001-bukrs.
  CALL FUNCTION 'FI_MESSAGE_COLLECT'
    EXPORTING
      i_fimsg = msgtab.
ENDFORM.                    "setup_currency
test if 2nd currency exists if user selected to display amounts      *
in 2nd Company code currency.                                        *
Also update the currencies_tab.                                      *
FORM test_currency USING
                         value(v_t001) STRUCTURE t001
                         p_success.
  CLEAR p_success.
  IF s_2curr = space.
    currency_tab-bukrs = v_t001-bukrs.
    currency_tab-waers = v_t001-waers.
    currency_tab-curtp = '10'.
    APPEND currency_tab.
    p_success = 'X'.
    EXIT.
  ENDIF.
  SELECT SINGLE * FROM t001a WHERE bukrs = v_t001-bukrs.
  CHECK sy-subrc = 0.
  CHECK t001a-curtp NE space.
  CASE t001a-curtp.
    WHEN '30'.                         " Group currency
      SELECT SINGLE * FROM t000  WHERE mandt = sy-mandt.
      CHECK sy-subrc = 0.
      CHECK t000-mwaer NE space.
      currency_tab-bukrs = v_t001-bukrs.
      currency_tab-waers = t000-mwaer.
      currency_tab-curtp = '30'.
      APPEND currency_tab.
    WHEN '40'.                         " Hard currency
      SELECT SINGLE * FROM t005 WHERE land1 = v_t001-land1.
      CHECK sy-subrc = 0.
      CHECK t005-curha NE space.
      currency_tab-bukrs = v_t001-bukrs.
      currency_tab-waers = t005-curha.
      currency_tab-curtp = '40'.
      APPEND currency_tab.
    WHEN '50'.                         " Index-based currency
      SELECT SINGLE * FROM t005  WHERE land1 = v_t001-land1.
      CHECK sy-subrc = 0.
      CHECK t005-curin NE space.
      currency_tab-bukrs = v_t001-bukrs.
      currency_tab-waers = t005-curin.
      currency_tab-curtp = '50'.
      APPEND currency_tab.
    WHEN '60'.                         " Global company currency
      SELECT SINGLE * FROM t880 WHERE rcomp = v_t001-rcomp.
      CHECK sy-subrc = 0.
      CHECK t880-curr NE space.
      currency_tab-bukrs = v_t001-bukrs.
      currency_tab-waers = t880-curr.
      currency_tab-curtp = '60'.
      APPEND currency_tab.
    WHEN OTHERS.  EXIT.
  ENDCASE.
  p_success = 'X'.
ENDFORM.                    "test_currency
    Set up chart of accounts                                         *
FORM set_up_chart USING value(v_t001) STRUCTURE t001
                        p_success.
  CLEAR p_success.
  IF s_chart = 'X'.                    " Normal chart of accounts
    charts_tab-bukrs = v_t001-bukrs.
    charts_tab-chart = v_t001-ktopl.
    CLEAR t004.
    SELECT SINGLE * FROM t004 WHERE ktopl = v_t001-ktopl.
    charts_tab-sakln = t004-sakln.
    IF charts_tab-sakln = 0.
      charts_tab-sakln = 10.
    ENDIF.
    APPEND charts_tab.
    p_success = 'X'.
    EXIT.
  ENDIF.
  IF s_altk = 'X'.                     " Alternative chart of accounts
    charts_tab-bukrs = v_t001-bukrs.
    IF v_t001-ktop2 = space.
      charts_tab-chart = v_t001-ktopl.
    ELSE.
      charts_tab-chart = v_t001-ktop2.
    ENDIF.
    CLEAR t004.
    SELECT SINGLE * FROM t004 WHERE ktopl = charts_tab-chart.
    charts_tab-sakln = t004-sakln.
    IF charts_tab-sakln = 0.
      charts_tab-sakln = 10.
    ENDIF.
    APPEND charts_tab.
    p_success = 'X'.
    EXIT.
  ENDIF.
  IF s_group = 'X'.                    " Group chart of accounts
    charts_tab-bukrs = v_t001-bukrs.
    CLEAR t004.
    SELECT SINGLE * FROM t004 WHERE ktopl = v_t001-ktopl.
    IF sy-subrc NE 0 OR t004-kktpl = space.
      CLEAR msgtab.
      msgtab-msort = '3'.
      msgtab-msgid = '00'.
      msgtab-msgty = 'E'.
      msgtab-msgno = '398'.
      msgtab-msgv1 = v_t001-bukrs.
      CALL FUNCTION 'FI_MESSAGE_COLLECT'
        EXPORTING
          i_fimsg = msgtab.
      EXIT.
    ENDIF.
    charts_tab-chart = t004-kktpl.
    CLEAR t004.
    SELECT SINGLE * FROM t004 WHERE ktopl = charts_tab-chart.
    charts_tab-sakln = t004-sakln.
    IF charts_tab-sakln = 0.
      charts_tab-sakln = 10.
    ENDIF.
    APPEND charts_tab.
    p_success = 'X'.
    EXIT.
  ENDIF.
ENDFORM.                    "set_up_chart
    Set up account                                                   *
FORM determine_account USING value(v_bukrs)
                             value(v_hkont)
                             p_hkont
                             p_success.
  CLEAR p_success.
If account ranges are given in company chart of accounts.
  IF s_acch = 'X' OR s_chart = 'X'.
    CHECK v_hkont IN s_akont.
  ENDIF.
  IF s_chart = 'X'.                    " Company accounts
    p_hkont = v_hkont.
    p_success = 'X'.
  ELSEIF s_altk = 'X'.                 " Alternative accounts
    PERFORM find_alternative_account USING v_bukrs v_hkont
                                           p_hkont p_success.
    CHECK p_success = 'X'.
  ELSE.                                " Group accounts
    PERFORM find_group_account USING v_bukrs v_hkont
                                     p_hkont p_success.
    CHECK p_success = 'X'.
  ENDIF.
  IF s_asch = 'X' AND s_chart NE 'X'.
    IF NOT ( p_hkont IN s_akont ).
      CLEAR p_success.
    ENDIF.
  ENDIF.
ENDFORM.                    "determine_account
Find alternative account                                             *
FORM find_alternative_account USING value(v_bukrs)
                                    value(v_hkont)
                                    p_alt_account
                                    p_success.
  DATA : altkt_not_found LIKE skb1-xkres.
  DATA : p_sakan LIKE ska1-sakan.
  DATA : ktext LIKE skat-txt20.
  DATA : ltext LIKE skat-txt50.
  DATA : text_not_found LIKE skb1-xkres.
  p_success = 'X'.
  CALL FUNCTION 'READ_SACHKONTO_ALTKT'
    EXPORTING
      bukrs           = v_bukrs
      saknr           = v_hkont
      xmass           = 'X'
      xskan           = 'X'
    IMPORTING
      altkt           = p_alt_account
      altkt_not_found = altkt_not_found
      altkt_sakan     = p_sakan
      ktext           = ktext
      ltext           = ltext
      text_not_found  = text_not_found
    EXCEPTIONS
      bukrs_not_found = 1
      saknr_not_found = 2
      OTHERS          = 3.
  IF altkt_not_found = 'X'.
    CLEAR msgtab.
    msgtab-msort = '1'.
    msgtab-msgid = 'FR'.
    msgtab-msgty = 'E'.
    msgtab-msgno = '274'.
    msgtab-msgv1 = v_hkont.
    msgtab-msgv2 = v_bukrs.
    CALL FUNCTION 'FI_MESSAGE_COLLECT'
      EXPORTING
        i_fimsg = msgtab.
    CLEAR p_success.
  ENDIF.
ENDFORM.                    "find_alternative_account
Find account according to group chart of accounts                    *
FORM find_group_account USING value(v_bukrs)
                                    value(v_hkont)
                                    p_group_account
                                    p_success.
  DATA : t001_wa LIKE t001.
  p_success = 'X'.
  CLEAR charts_tab.
  READ TABLE charts_tab WITH KEY bukrs = v_bukrs.
  SELECT SINGLE * FROM t001 INTO t001_wa WHERE bukrs = v_bukrs.
  SELECT SINGLE * FROM ska1 WHERE ktopl = t001_wa-ktopl AND
                           saknr = v_hkont.
  p_group_account = ska1-bilkt.
  IF sy-subrc NE 0 OR ska1-bilkt = space.
    CLEAR msgtab.
    msgtab-msort = '4'.
    msgtab-msgid = 'FR'.
    msgtab-msgty = 'E'.
    msgtab-msgno = '274'.
    msgtab-msgv1 = v_bukrs.
    msgtab-msgv2 = v_hkont.
    CALL FUNCTION 'FI_MESSAGE_COLLECT'
      EXPORTING
        i_fimsg = msgtab.
    CLEAR p_success.
  ENDIF.
ENDFORM.                    "find_group_account
SPOT
Collect information from lfc1                                       *
FORM collect_lfc1 USING value(pbukrs).
  DATA : amount LIKE lfc1-um01s.
  DATA : l_success.
  SELECT * FROM lfc1 WHERE bukrs = pbukrs AND
                           lifnr IN s_lifnr AND
                           gjahr = s_gjahr.
    CLEAR f_group.
    f_group-bukrs = lfc1-bukrs.
    f_group-lifnr = lfc1-lifnr.
  { au1++
    CLEAR: lfa1, lfb1.
    SELECT SINGLE * FROM lfa1 WHERE lifnr = lfc1-lifnr.
    call function 'J_1GACCOUNT_AUTH_CHECK'
      exporting
        i_xdb            = 'K'
        i_begru          = lfa1-begru
        i_aktvt          = '03'
      exceptions
        no_authorization = 1
        others           = 2.
    check sy-subrc = 0.
  } au1
    SELECT SINGLE * FROM lfb1 WHERE lifnr = lfc1-lifnr AND
                                    bukrs = pbukrs.
    IF sy-subrc NE 0.
      f_group-akont = '##########'.
    ELSE.
      PERFORM determine_account USING pbukrs lfb1-akont
                                f_group-akont l_success.
      CHECK l_success = 'X'.
    ENDIF.
  { au1++
    call function 'J_1GACCOUNT_AUTH_CHECK'
      exporting
        i_xdb            = 'K'
        i_begru          = lfb1-begru
        i_aktvt          = '03'
      exceptions
        no_authorization = 1
        others           = 2.
    check sy-subrc = 0.
  } au1
    f_group-umskz = space.
    IF lfc1-umsav NE 0 AND s_rprevy = 'X'.
      f_group-balancel = lfc1-umsav.      "BCF
      f_group-id = '1'.
      EXTRACT daten.
    ENDIF.
    IF last_previous_period > 0.
      CLEAR : amount, f_group-debitl, f_group-creditl,
              f_group-balancel.
      DO last_previous_period TIMES
         VARYING amount FROM lfc1-um01s NEXT lfc1-um02s.
        ADD amount TO f_group-debitl.
      ENDDO.
    f_group-debitl = abs( f_group-debitl ).
      CLEAR amount.
      DO last_previous_period TIMES
         VARYING amount FROM lfc1-um01h NEXT lfc1-um02h.
        ADD amount TO f_group-creditl.
      ENDDO.
    f_group-creditl = abs( f_group-creditl ).
      IF ( f_group-debitl NE 0 OR f_group-creditl NE 0 ) AND
         ( s_rprevd = 'X' ).
        f_group-balancel = f_group-debitl - f_group-creditl.
        f_group-id = '2'.
        EXTRACT daten.
      ENDIF.
    ENDIF.
  ENDSELECT.
ENDFORM.                    "collect_lfc1
SPOT
Collect information from KNC1                                       *
FORM collect_knc1 USING value(pbukrs).
  DATA : amount LIKE knc1-um01s.
  DATA : l_success.
A.NEZ
  select * from lfa1 where lifnr in s_lifnr.
*ilifnr-kunnr = lfa1-kunnr.
*append ilifnr.
*clear: ilifnr.
*endselect.
  LOOP AT ilifnr.
    SELECT * FROM knc1 WHERE bukrs = pbukrs AND
                             kunnr = ilifnr-kunnr AND
                             gjahr = s_gjahr.
      CLEAR f_group.
      f_group-bukrs = knc1-bukrs.
      f_group-kunnr = knc1-kunnr.
  { au1++
      CLEAR: kna1, knb1.   "SPOT K
      SELECT SINGLE * FROM kna1 WHERE kunnr = knc1-kunnr.
    call function 'J_1GACCOUNT_AUTH_CHECK'
      exporting
        i_xdb            = 'D'
        i_begru          = kna1-begru
        i_aktvt          = '03'
      exceptions

PLEASE HELP

Similar Messages

  • Who has had a problem with Zen Firmware upgra

    Its difficult when reading through the?message boards to get a true reflection of what is happening, clearly quite a number of people have had problems after and during the process of upgrading firmware, others clearly have not, I am interested to see how wide spread the problem is. Now clearly to some degree there are going to be more people on a site like this with a problems, those who have upgraded without any difficulties are blissfully unaware. So if you have a problem just post a yes I am sure you have vented your frustration in a myriad of posts elsewhere anywhere this is purely an attempt to gauge the size of the problem.

    Well it now appears Creative want to charge me ?83.43 to fix there problem thats putting it politely, I am planning to contact the IT Press to see how widespread this problem is please add to this post if you are having problems with the latest firmware release.

  • New to everything: Macbook Pro, Logic 9. Any patient, smart people to help?

    Hello world
    I finally bit the bullet, bought the computer and the software, and want to make my music permanent (I will be hoping to record using both organic instruments and vst's). But....I really have no idea where to begin. I know all of these unconnected things about set-ups and music recording, but can;t seem to bring it together.
    So I have some questions, and I need someone who is patient, intelligent, and can break it down into newbie terms for this sort of thing. I'm hoping thats where you come in.
    1. What do I need to get started? I know I need a Firewire interface, but I'm not sure why. How is this different than a mic preamp? Are they interchangeable?
    I have heard I should use external drives for sample (ex. Komplete), but don't know how. I just read that some people have loaded Logic 9 on an external drive, but I don;t know why or how. I don;t want to screw it up. The shipment comes tomorrow.
    2. What sort of other "before I load anything" things should I know? Again, I want to get it right before I put anything on the computer. For example, is boot camp something I want to consider right at the start, or can that wait? I have a copy of Windows 7 from my other computer that I can use.
    3. Back to the drive question. I got the 17" because of the express card slot and I figured that I would be able to expand for whatever I need, but again, I really don;t know what it is that i MIGHT need. I have read but don;t understand about eSATA drives.
    4. The last thing to consider is that I want this to be a performance mobile rig, too. In other words, I want to (hopefully) use Mainstage to play my guitar and keyboard through the MBP. This being said, I am worried that if I use all of these other drives, then it's going to be a jumble of wires and daisy chains that makes me anxious to think about in a live, "setting-up" situation.
    I'll stop there, because it continues on. Please know that I have spent the better part of the past year reading forums and trying to figure this out, but again, it's all kind of in the ether, floating around, not making cohesive sense. I'm just exited to have finally gotten the **** computer.
    It;s only up from here. Thanks in advance.

    We're all patient and smart in here. Except ErikSimon. Don't listen to a word he says But seriously...
    First up, don't worry. You have a good machine arriving and the technology will work. There will be a learning curve and some hurdles, but that's to be expected. On to your points:
    1. An audio interface (Preferably Firewire, but USB can be OK) in it's simplest form is a way of getting high quality audio in and out of your computer (via either XLR/TRS/phono/digital etc). They are totally separate things from mic preamps BUT many interfaces (most) have mic preamps incorporated into them. But a mic preamp is a separate box otherwise, designed for powering a microphone and won't be any good to your computer on it's own. Hope that clarifies.
    Always install Logic on the internal system drive. Any external drives are only for recording/storing audio or for large sample libraries (e.g. Logic Jam-packs & Komplete). They should also be as fast as possible (7,200rpm) and running via firewire (prefarbly not daisychained).
    2. As mentioned, not sure why you want to install Windows. You mentioned VST's earlier... be aware Logic uses AU's instead. Before you install anything, run every single software update Apple has to offer, then 'repair disk permissions' in 'disc utilities'. Then install any drivers for interfaces etc. then Logic, but you can add interfaces later without any problems.
    3. I can't advise you on this.
    4. Yes you can take the rig out as a mobile setup. I do it regularly and, it can be a pain but it's perfectly normal. Under these circumstances you will want to consider reducing the setup to take out for various reasons... above all it minimizes risk of crashes etc and also it's usually not necessary to have everything running live on stage: consider backing tracks etc and running it from the internal drive.
    Hope this helps to some extent.

  • Use the calendar during call?

    I wonder if there is a way to use the calendar during a phone call?
    It's difficult not be able to use that funktion on a work mobile.
    Is there a solution?
    Solved!
    Go to Solution.

    ok this is what you can do
    you can go to :
    tools- settings-general- personalization-standby mode- shortcuts
    one of my shortcuts is a calendar and one is a contacts right and left key...when you are on a call all you have to do in order to be able to text and use calendar and other functions is to press the left option button and select -go to standby menu from there you can do pretty much everything you want or need while on a call. i hope this helps
    in order to see how this works you can call a friend who is patient and/or yourself and see how this works out
    Message Edited by radical24 on 17-Dec-2008 04:51 PM
    You know what I love about you the most, the fact that you are not me ! In love with technology and all that it can offer. Join me in discovery....

  • Customer service issues

    I am having significant issues getting u-verse installed with the rate and equipment promised when I signed up (which have record of via chat).  One the day prior to installation I talked to an Esther in Customer Service in San Antonio who confirmed my appointment and guaranteed a 1TB DVR would be delivered with the installer for installation.  The installer (Tracy Pickett #TP8522, super polite) came to my house on 6/17 without the 1TB DVR I was promised and the service was provisioned for neighbor’s house.  That was going to double the time for installation, plus no 1TB DVR, so I told the installer I would reschedule.  That day I talked with a difficult character who told me he was in "Ghalla" (India?) named James who was difficult to understand and extremely rude, but he promised me a 1TB DVR, but could not get the agreed upon month rate correct (again guaranteed in writing via chat).  He told me it would be $25 more per month than agreement.  He then transferred me to a Kim in Retention in Jackson, MS who got the price right, but included a $49.95 install fee with 1TB DVR.  She said I was all ready and good to go, but she was going to talk to her supervisor about getting the installation fee waived and additional credits for my troubles that day and with James who she agreed was very difficult to deal with when she conversed with him.  She promised a return phone call from supervisor by end of the day…13 days later, No Call.  The following week I called Customer Service again and after going through several people ended up with rep named Princess in Retention in San Antonio.  She was not the friendliest character telling me AT&T did not even offer a 1TB DVR and that I would need to check with DirecTV since they are the only provider that offers such equipment.  I proceeded to tell her of my original chat, conversations with Esther, Kim and James as well as my installer, Tracy, all telling me a 1TB was available.  While talking on phone I googled it and found it was available, but she still continued to deny availability.  Finally she contacted technical support and told me it was available, but I would have to talk to the sales department.  I told her I was working with her, so she contacted sales which stated I would have to take a regular DVR and then “request” a 1TB DVR after installation.  I told her that was not going to happen since it was promised to me up front and what’s to say I was going to get it once service was ongoing and I was locked in.  She stated she would have her supervisor, Roland, call me within one hour...still No Call.  Essentially I want to switch to your product from a competitor, but your employees are making it extremely difficult.  I treat each one of them with the utmost respect, but obviously it’s not reciprocal.  This is my last effort to get service, if this doesn’t work out I am going to just cancel and stay with my current provider.  Please help!

       That the exact problem w/chat, everything gets jumbled up.  ATT does have a 1TB DVR, but only for Gigapower users, no one else.
    Chris
    Please NO SD stretch-o-vision or 480 SD HD Channels
    Need Help? PM ATT Uverse Care (all service problems)
    ATT Customer Care(all other problems)
    Your Results May Vary, In My Humble Opinion
    I Call It Like I See It, Simply a U-verse user, nothing more

  • How to set up Bonding on CentOS 6.2 with Linux Integration Services 3.4

    Having a hard time setting up bonding to work on a vm running CentOS 6.2. LinuxICv34.iso is installed.  Using three network adapters.
    Prior to os install I configured the three Network Adapters with the following settings:
    ***Via Virtual Switch Manager:
    Connection Type: External Network, Allow management os to share network adapter
    VLAN ID: Unchecked
    SR-IOV: Unchecked (Unsupported on host)
    Extensions: MS NDIS Capture = Unchecked | MS Windows Filtering Platform = Checked
    ***Via VM Settings:
    For all adapters:
    VLAN ID and Bandwidth Management is unchecked.
    In Hardware Acceleration, Enable virtual machine queue is checked, Enable IPsec task offloading is checked, and maximum number is 4096. Additionally, Enable SR-IOV is unchecked.
    In Advanced Features, a Static Mac address is assigned and Enable Mac address spoofing is checked, DHCP Guard is unchecked, Router guard is unchecked, Port mirroring is None, and NIC Teaming is checked.
    Mac Address for each Adapter:
    Network Adapter 1: 00:25:0D:20:20:1A
    Network Adapter 2: 00:25:0D:20:20:1B
    Network Adapter 3: 00:25:0D:20:20:1C
    After the os and LinuxICv34.iso was installed, I set up networking access on eth0 by making the following changes:
    vi /etc/sysconfig/network-scripts/ifcfg-eth0
    DEVICE="eth0"
    HWADDR="00:25:0D:20:20:1A"
    NM_CONTROLLED="no"
    ONBOOT="yes"
    BOOTPROTO="static"
    IPADDR="10.1.1.110"
    NETMASK="255.255.255.0"
    GATEWAY="10.1.1.100"
    DNS1="10.1.1.105"
    DNS2="10.1.1.106"
    Then:
    vi /etc/sysconfig/network
    NETWORKING=yes
    HOSTNAME=MyCentOS6.MyActiveDirectoryDomain
    GATEWAY=10.1.1.100
    and finally:
    vi /etc/resolv.conf
    nameserver 10.1.1.105
    nameserver 10.1.1.106
    I entered service network restart and was able to ping google.com so I then moved on to setting up eth1, eth2, and bond0.
    DEVICE="eth1"
    HWADDR="00:25:0D:20:20:1B"
    NM_CONTROLLED="no"
    ONBOOT="yes"
    MASTER="bond0"
    SLAVE="yes"
    USERCTL="no"
    DEVICE="eth2"
    HWADDR="00:25:0D:20:20:1C"
    NM_CONTROLLED="no"
    ONBOOT="yes"
    MASTER="bond0"
    SLAVE="yes"
    USERCTL="no"
    DEVICE="bond0"
    USERCTL="no"
    BOOTPROTO="none"
    ONBOOT="yes"
    IPADDR="10.1.1.110"
    NETMASK="255.255.255.0"
    BONDING_OPTS="miimon=100 mode=balance-alb"
    TYPE="Bonding"
    I then went back into eth0 and changed it to:
    DEVICE="eth0"
    HWADDR="00:25:0D:20:20:1A"
    NM_CONTROLLED="no"
    ONBOOT="yes"
    #BOOTPROTO="static"
    #IPADDR="10.1.1.110"
    #NETMASK="255.255.255.0"
    #GATEWAY="10.1.1.100"
    #DNS1="10.1.1.105"
    #DNS2="10.1.1.106"
    MASTER="bond0"
    SLAVE="yes"
    USERCTL="no"
    Next I added file /etc/modprobe.d/bonding.conf per CentOS 6 instructions, and wrote the following line on the file:
    alias bond0 bonding
    I then entered service network restart and expected everything to work, but instead received these error messages:
    ADDRCONF(NETDEV_UP): bond0: link is not ready
    bonding: bond0: Error: dev_set_mac_address of dev eth0 failed! ALB mode requires that the base driver support setting the hw address also when the network device's interface is open
    bonding: bond0: Error: dev_set_mac_address of dev eth1 failed! ALB mode requires that the base driver support setting the hw address also when the network device's interface is open
    bonding: bond0: Error: dev_set_mac_address of dev eth2 failed! ALB mode requires that the base driver support setting the hw address also when the network device's interface is open
    I have tried commenting out the mac addresses, USERCTL=no and NM_CONTROLLED=no in the ifcfg files but that hasn't helped.
    I'm running out of ideas... Can anyone give me some tips?
    Much appreciated~

    Hello ECase,
    i known my answer is probably too late but maybe it can help others who are having the same difficulties. My setup looks almost like yours and I did the same steps as you did. Unfortunately with exactly the same results.
    What helped in my case was to change the teaming mode.
    These are the modes available in CentOS:
    mode=0 (Balance-rr) –
    This mode provides load balancing and fault tolerance.
    mode=1 (active-backup) –
    This mode provides fault tolerance.
    mode=2 (balance-xor) –
    This mode provides load balancing and fault tolerance.
    mode=3 (broadcast) –
    This mode provides fault tolerance.
    mode=4 (802.3ad) –
    This mode provides load balancing and fault tolerance.
    mode=5 (balance-tlb) –
    Prerequisite: Ethtool support in the base drivers for retrieving the speed of each slave.
    mode=6 (balance-alb) –
    Prerequisite: Ethtool support in the base drivers for retrieving the speed of each slave.
    Mode 0 -4 worked great while mode 5 and 6 don't work at all. So if you try bonding on a CentOS guest in Hyper-V keep mode between 0 and 4
    Regards

  • Removing credit card info

    Thank you Steve (RIP),
    You have managed to hire people, who want to make it difficult for consumers to remove credit card info from itunes. RANT OVER.
    How in the H.E. double hockeysticks do you remove credit card info in itunes 10.6? Why do I need to fill out a form to remove my credit card info from itunes?
    Why do I have to jump through so many hoops just to remove my credit card info?

    Quick and easy way:
    Open iTunes
    Go to Account
    Click on "Edit" next to Payment type
    Choose "None"
    Click on "Done"

  • Error #2007

    These are the code for the php and flash page:
    <?
    // Create local variables from the Flash ActionScript posted variables
    $senderName   = $_POST['userName'];
    $senderEmail     = $_POST['userEmail'];
    $senderMessage = $_POST['userMsg'];
    // Strip slashes on the Local variables for security
    $senderName   = stripslashes($senderName);
    $senderEmail     = stripslashes($senderEmail);
    $senderMessage   = stripslashes($senderMessage);
    // IMPORTANT - Change these lines to be appropriate for your needs - IMPORTANT
    $to = "[email protected]";            
    $from = "$senderEmail";
    $subject = "Contact from gharweg.org.uk";
    // Modify the Body of the message however you like
    $message = "Message from Gharweg.org.uk:
    Their Name:   $senderName
    Their Email:   $senderEmail
    Their Message is below:
    $senderMessage";
    // Build $headers Variable
    $headers = "From: $from\r\n";
    $headers .= "Content-type: text\r\n";
    $to = "$to";
        // Send the email
        mail($to, $subject, $message, $headers);
        // Assemble the message that goes back to Flash
        // The flash ActionScript is looking for a return variable of "return_msg"
        $my_msg = "Thanks $senderName, your message has been sent.";
        // Print the data back to flash who is patiently waiting for it in the onCompleteHandler
        print "return_msg=$my_msg";
    // Exit script   
    exit();
    ?>
    // Set text formatting colors for errors, waiting..., and success mechanisms
    var errorsFormat:TextFormat = new TextFormat();
    errorsFormat.color = 0xFF0000;
    var waitingFormat:TextFormat = new TextFormat();
    waitingFormat.color = 0x001111;
    var successFormat:TextFormat = new TextFormat();
    successFormat.color = 0x3366FF;
    // hide the little processing movieclip
    processing_mc.visible = false;
    // Assign a variable name for our URLVariables object
    var variables:URLVariables = new URLVariables();
    //  Build the varSend variable
    var varSend:URLRequest = new URLRequest("new/contact_parse.php");
    varSend.method = URLRequestMethod.POST;
    varSend.data = variables;
    // Build the varLoader variable
    var varLoader:URLLoader = new URLLoader;
    varLoader.dataFormat = URLLoaderDataFormat.VARIABLES;
    varLoader.addEventListener(Event.COMPLETE, completeHandler);
    // Handler for PHP script completion and return
    function completeHandler(event:Event):void{
        // remove processing movieclip
        processing_mc.visible = false;
        // Clear the form fields
        name_txt.text = ".";
        email_txt.text = ".";
        msg_txt.text = "-";
        // Load the response from the PHP file
        status_txt.text = event.target.data.return_msg;
        status_txt.setTextFormat(successFormat);
    // Add an event listener for the submit button and what function to run
    submit_btn.addEventListener(MouseEvent.CLICK, ValidateAndSend);
    // Validate form fields and send the variables when submit button is clicked
    function ValidateAndSend(event:MouseEvent):void{
        //validate form fields
        if(!name_txt.length) {   
            status_txt.text = "Please enter your name.";   
            status_txt.setTextFormat(errorsFormat);
        } else if(!email_txt.length) {
            status_txt.text = "Please enter an email address";
            status_txt.setTextFormat(errorsFormat);
        } else if(!validateEmail(email_txt.text)) {
            status_txt.text = "Please enter a VALID email address";
            status_txt.setTextFormat(errorsFormat);
        } else if(!msg_txt.length) {
            status_txt.text = "Please enter a message.";
            status_txt.setTextFormat(errorsFormat);
        } else {
            // All is good so send the message to the parse file
            // Show the little "processing_mc" movieclip
            processing_mc.visible = true;
            // Ready the variables for sending
              variables.userName = name_txt.text;
               variables.userEmail = email_txt.text;
               variables.userMsg = msg_txt.text;  
            // Send the data to the php file
               varLoader.load(varSend);
            // Put a temporary message in the response field while the PHP file sends back
            // If the code does not connect to the PHP file this message will remain visible to user
            status_txt.text = "Waiting for server connection...";
            status_txt.setTextFormat(waitingFormat);
        } // close else after form validation
    } // Close ValidateAndSend function //////////////////////////////////////////////////////////////
    // Validate email function
    function validateEmail(str:String):Boolean {
        var pattern:RegExp = /(\w|[_.\-])+@((\w|-)+\.)+\w{2,4}+/;
        var result:Object = pattern.exec(str);
        if(result == null) {
            return false;
        return true;

    When you get error messages and post about them, you should include the entire error message in your posting.  In my case I have no idea what a 2007 error involves.  Also, to get the most info into your error messages you should enable the option to Permit Debugging found in the Flash section of the file's Publish Settings.  Selecting that option can often add more details into the error message.

  • ITunes 10.5 on Windows 7 freezes....constantly? PLEASE HELP A.S.A.P!

    I don't know how to fix this. I've contacted iTunes support over the phone and it still does it, but now not AS frequently, but let me explain.....
    Okay, well. I have had iTunes since the iTunes 9. Personally, iTunes bugs the living crap out of me. But that's besides the point. Ever since I've updated to iTunes 10.4, almost every time I try to open iTunes it opens but then freezes. It never connects to the Apple Store anymore (it freezes in the middle of it), and now updating to 10.5 it freezes upon opening CONSTANTLY. There has not been a time it has not froze on opening. I can't sync my music OR my apps to my new white iPod because of this. I have to be very patient (which is difficult for me ) and I have to wait for it to unfreeze (sometimes it never does) and work through whatever I'm doing VERY slowly. Can ANYBODY help me? I am so frustrated!! Sorry for the long explanation, I wanted it as detailed as possible. I never get any error messages. Is it my computer and if it is how do I fix it?! I've uninstalled/reinstalled iTunes, which didn't work.
    PLEASE HELP!!!!!!!!!!!!!!!!!

    Peter Hah
    After spending another two days on pinning down the iTunes 10.5 blank store page problem, here's the solution to be found: https://discussions.apple.com/thread/3372617?start=0&tstart=0
    Look out for "japiohelp".
    In short:
    a) press Windows key + "R", enter "cmd", and press Ctrl+Shift+Enter (= runs as admin)
    b) enter "netsh winsock reset" and pres enter
    c) reboot the computer
    and Bob's your uncle.
    P.

  • Ipod(s) are not syncing with itunes all of a sudden

    WARNING, this is going to be very long-winded.  So I've exhausted every avenue I can think of myself, so I figured I'd try just asking on the forum here and hopefully someone can suggest a solution.  First, the specs of the equipment/software involved:
    Windows 7 64 bit O.S. on my pc
    Itunes 10.3.1.55
    Ipod touch 4thGen 64GB
    Ipod Nano 4thGen 8GB
    So a couple days ago, I tried syncing my ipod touch to my pc, and it wasn't recognized by itunes, it wasn't even recognized by Windows as an ipod.  It doesn't even charge the ipod or light up the screen.  All that happens when I plug it into the sync cable is that after about 10-15 seconds I get a windows error saying "USB device not recognized"  Under windows device manager, in the USB devices section, when the ipod(s) are connected it shows an unknown device connected to the port, but when I right click and look at the details for the unknown device, it gives no indication whatsoever that it is an apple device, doesn't say anything about AppleMobileDevice, or anything like that, just everything about it is unknown as far as windows is concerned.  The catch is, my ipod Nano is getting the exact same result, so if it's a hardware issure with the ipod itself, it struck both my ipods at the exact same time.  So I went to work investigating and troubleshooting.  After reading through the troubleshooting guides on apples website, some exhaustive google searches, consulting with a few people I know who work in I.T. troubleshooting, and reading through this forum for several hours looking for related issues, here is what I've tried:
    1. My pc has 6 usb ports, I've tried using both cables (I have the syncing cables that came with each Ipod) with each Ipod in each USB port.
    2. I've tried resetting both Ipods
    3. I've uninstalled all apple software from my pc, rebooted, reinstalled.
    4. I repeated step 3 but tried installing an older version of itunes (one that I know worked).
    5.  I tried every step I could find suggested by Itunes on the apple support website:  Tried manually uninstalling/reinstalling the driver to the usb device, tried uninstalling the device driver while it was connected and rebooted (leaving it connected) hoping that windows would automatically install the right driver at startup.
    6.  Suspecting it may have been virus related, I've run exhaustive searches for malware/viruses with several different antivirus/antimalware/antirootkit programs using them in and out of windows safemode.
    7.  I did a windows system restore to a restore point back over a week ago, well before I started having issues.
    8.  I emailed apple support and explained the problem in detail, the sent me a link to the "applecare express service".  That was extremely helpful...
    9.  I took my ipod touch, and both my syncing cables over to a friends house and did the following:  Tried syncing it with his pc, he has the same exact version of windows and itunes as me, and it worked fine.  It synced immediately and recognized the device without any problem whatsoever.  While I had it synced to his pc, I master reset it back to factory settings, took it home and tried syncing it to my pc again to no avail. 
    10.  I tried very politey asking it to please sync with my pc.
    11.  I plugged it into my stereo which has a built in ipod dock, and it works fine with that device, charges, plays music off the ipod.
    I'm willing to consider buying one of the "pay-per-incident" help feature service things from Apple Express lane, if I thought it would help at all. 
    So, to anyone who was patient enough to read through all of that, any suggestions as to what the problem might be?  I'm still assuming at this point that it has to be something software related, I just have no idea what, and can't think of a single thing that changed on my pc from when I synced it on tuesday morning, to when I tried to sync it on wednesday morning and this all started. 

    FIXED!
    Follow up for anyone who reads this post and has encountered the same/roughly the same type of error.  To recap basically what happened was one day Itunes on my pc with win7 64bit was working fine and syncing up with both my ipods (ipod touch and ipod nano) and the next day it wasn't working at all.  What happened was when I tried to sync either device with my pc, not only did the proper drivers not install/function, but they wouldn't even charge.  Well I spent some long hours trying to figure what was going on, wound up going so far as to format my hard drive (i had my data backed up first!) and do a clean install of windows 7, and even that still didn't fix it.  In my frustration I decided to try to plug in some other USB devices I had lying around but hadn't used in awhile, (microsoft HD webcam, and a flash memory storage drive) and discovered I got the same exact error/symptoms with those devices, i.e. drivers failed to install in Win7.  So now I realized that whatever was going on was beyond just itunes/ipods, and something was wrong on a systematic level.  Basically, certain USB devices were functioning perfectly fine (mouse, keyboard, x360 controller) while others (ipods, webcam, flash drive) weren't functioning at all. 
    So what was the solution?  Someone suggested trying adding a stand alone USB add on card.  For those that don't know, it's a card you can plug into an available slot in your motherboard and it adds USB ports to a pc that otherwise doesn't have any, or adds extra ports to your current setup.  I picked up a card at best buy for $20 that plugged into an available PCI slot, gave me two new available USB ports. (set-up is VERY easy for these cards, there is no set-up really, you just plug the card in and turn the pc back on)
    VOILA!, after installing the new USB card, I opened Itunes, plugged in my ipod touch, and it synced up right away, I was so relieved.  I still have no idea what caused the USB device/driver issues, or why adding the extra card worked, but it was a cheap and easy solution, and hopefully if anyone else encounters a similar "unsolveable" problem, this might help them.

  • Setting Up a Shared Address Book

    Hello, and thank you for taking a look at my question.
    I concur with the many people on this forum who are amazed how frustratingly difficult it is to setup a shared Address Book. I have a small office network of 4 users (all running the latest Snow Leopard) connected to a Mac Pro running the most current Snow Leopard Server.
    This forum did lead me to 2 good articles on the subject:
    http://osxupgrade.com/create-a-global-address-book-with-mac-os-x-snow-leopard-se rver/456/
    http://translate.google.com/translate?js=y&prev=_t&hl=en&ie=UTF-8&layout=1&eotf= 1&u=http%3A%2F%2Fsupport.osxplain.de%2Fcontent%2F4%2F1%2Fde%2Fgruppenkontakte.ht ml&sl=de&tl=en
    I followed them carefully and created my new Group in Workgroup Manager which I then populated with the users in my office.
    I then tried to configure Address Book at the client's iMac. I couldn't get Address Book to 'see' the server.
    There are 2 areas I may have got wrong and I would be very grateful for some advice/guidance please:
    On the client Mac, how can I check the fully qualified address of my server to ensure I am entering the correct address in the Address Book Wizard when creating the new account (can I not use the static IP address of the server)?
    On the server, I have created, and started, the Address Book Server service. What should I enter in the Authentication > Host Name please? The manual says "It should be a fully qualified domain name matched with a reverse lookup record". How can I check I have got this correct?
    Sorry for the obvious questions but it's all new to me.
    Many thanks
    Chris

    On the client Mac, how can I check the fully qualified address of my server to ensure I am entering the correct address in the >Address Book Wizard when creating the new account (can I not use the static IP address of the server)?
    Open the Terminal window on your client Mac and type *dig [name of your server]* and check that it returns the IP address of your server. Then type *dig -x [ip address of your server] and check it returns the name of your server e.g. server.domain.com
    This will show you what your client Mac thinks you server is.
    Do the same on the server and it should match. If not then you may have a problem. Here is an example.
    *dig server.bumfodder.com*
    ; <<>> DiG 9.6.0-APPLE-P2 <<>> server.bumfodder.com
    ;; global options: +cmd
    ;; Got answer:
    ;; ->>HEADER<<- opcode: QUERY, status: NOERROR, id: 49014
    ;; flags: qr rd ra; QUERY: 1, ANSWER: 1, AUTHORITY: 0, ADDITIONAL: 0
    ;; QUESTION SECTION:
    ;server.bumfodder.com. IN A
    ;; ANSWER SECTION:
    server.bumfodder.com. 37694 IN A 95.130.103.213
    ;; Query time: 11 msec
    ;; SERVER: 192.168.0.1#53(192.168.0.1)
    ;; WHEN: Mon Sep 20 07:46:43 2010
    ;; MSG SIZE rcvd: 54
    *dig -x 95.130.103.213*
    ; <<>> DiG 9.6.0-APPLE-P2 <<>> -x 95.130.103.213
    ;; global options: +cmd
    ;; Got answer:
    ;; ->>HEADER<<- opcode: QUERY, status: NOERROR, id: 25816
    ;; flags: qr rd ra; QUERY: 1, ANSWER: 1, AUTHORITY: 0, ADDITIONAL: 0
    ;; QUESTION SECTION:
    ;213.103.130.95.in-addr.arpa. IN PTR
    ;; ANSWER SECTION:
    213.103.130.95.in-addr.arpa. 38400 IN PTR server.bumfodder.com.
    ;; Query time: 36 msec
    ;; SERVER: 192.168.0.1#53(192.168.0.1)
    ;; WHEN: Mon Sep 20 07:47:46 2010
    ;; MSG SIZE rcvd: 79
    <div class="jive-quote">On the server, I have created, and started, the Address Book Server service. What should I enter in the Authentication > >Host Name please? The manual says "It should be a fully qualified domain name matched with a reverse lookup record". >How can I check I have got this correct?
    In the above example - you would put server.bumfodder.com

  • Another I don't what to do to get BT to sort it ou...

    On Wednesday morning we lost our BT Broadband connection. I figured this was something to do with the engineers doing the cabling work in our village ready for the imminent launch of Infinity so phoned up BT who had me carrying out allsorts of things to test various causes and told me it wouldn't be down to the upgrade work being carried out locally to us.
    After this call, which resulted in nothing being resolved, I realised that while I had a dial tone on the domestic landline that the broadband shares when I called my mobile the caller display showed a local number calling that wasn't mine! When I then called my landline number I got through to someone elses home! So, back on the phone to BT who after more messing about trying different things said they'd send someone out the next day (with the usual threat that I'd get a bill for £130 if it was down to my equipment) although it probably had nothing to do with the local work being carried out.
    I decided I'd go and have a word with BT's sub-contractor while he was sat in his manhole round the corner from our house and he confessed that they'd been disconnecting and reconnecting some older style non-colour coded cables for our road that morning and apologetically told me it was probably down to an error on their part but I'd have to wait for the booked BT engineer to come out to trace and fix the mis-connection.
    The engineer was due to come between 8am-1pm and eventually turned up at 12.55pm. Told him the problem and after some to and fro-ing between us and the exchange, he fits new twinport Openreach Mk3 socket while here and announces all fixed. So I check the landline - sorted, check the broadband - nothing. He plugs something in and tells me the line is fine on his equipment and I'll need to call BT again and off he trots, no longer his problem.
    That afternoon I spent nearly 3 hours on the phone to BT's broadband 'support' in India or whereever they are. I keep telling them it's going to be down to the line mix-up but no, I'm told its not and after nearly 3 hours - in which they want to connect remotely without me having a broadband connection!!!) I'm told it must be down to my Netgear router (thats been faultless for all the time I've had it) and I need to speak to Netgear to configure it correctly. I've never messed with it so I can't see why its suddenly configured incorrectly. Anyway, I then spend an age on the phone to Netgear and the router is fine. But still not broadband connection.
    Out of frustation I decided to go and buy a brand new BT Homehub 4R and guess what? Still no connection so there's £50 wasted. Unfortunately by then its late evening but I'm onto BT the following morning, Friday. More messing about and eventually I'm told its a line error but it will be sorted by 4.30pm the next day, maybe before, and I'll receive a phone call to confirm.
    4.30pm Saturday and I get a call saying they need me to do all the things I've already done. Still nothing, my line is fine apparently - usual threat of £130 bill if they send someone out and its my equipment - but they'll call me back on Sunday. Not acceptable so they'll call me back in a couple of hours.
    Do I have any faith in a positive outcome in this forthcoming phone call? None at all. This problem all started when their sub-contractor messed up the line disconnection/reconnection in the villages network upgrade and that's where I'd bet my mortgage the broadband problem lies. Does anyone have any idea how I can get someone at BT (ideally in the UK rather than reading from a script in India) to understand this and resolve it? I've wasted hours and hours waiting for the engineer and on the phone. I work from home and need broadband as 95% of my customer enquiries come via the net. I'm at my wits end now.

    The landline is now okay.
    I've tried the top socket on the new master and they've also had me unscrew and remove the front and plug in via a filter to the socket the whole front part normally plugs into and it made no difference.
    I'm a sole trader and while I have a separate business landine the normal home broadband is normally sufficent for what I need. Having both a personal and business broadband would be overkill but I can imagine what the inland revenue would say about all the personal use family would take up on a business broadband. Either way, if you pay for a service you should get it not be faffed around to such an extent with all manner of excuses when I know full well it's all down to the original mess up on the connections between us and the exchange. If I do end up having to take out a business broadband service it will be with anyone but BT and my business phone line will be going the same way. The only time I briefly felt like any progress was being made was when I called from my BT business landline and got through to someone in the UK business section who listened patiently before passing me through to the usual domestic broadband script readers.

  • Horizontal Scroll Bar

    I have this site that I'm practicing on called
    Massattack Studios,
    it's been a work in progress for a while experimenting with Flash
    and Dreamweaver 8.
    In internet explorer my scroll bar situation works fine, in
    Fire Fox the unwanted horizontal scroll bar appears. At least at
    the moment I'm not concerned with other browsers. Can anybody tell
    me how to get rid of that little guy?
    I'm looking at the Validator and it is very overwealming to
    me as a beginner with the code.
    Any help would be great, i can post anything you may need to
    figure it out, thank you very much!
    This is my main index page...
    <!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Frameset//EN"
    http://www.w3.org/TR/xhtml1/DTD/xhtml1-frameset.dtd">
    <html xmlns="
    http://www.w3.org/1999/xhtml">
    <head>
    <title>Massattack Studios</title>
    <meta http-equiv="Content-Type" content="text/html;
    charset=iso-8859-1" />
    </head>
    <frameset cols="*,650,*" border="0">
    <frame src="left.htm" name="left" marginwidth="0"
    marginheight="0" scrolling=no>
    <frameset rows="100,*,25" border="0">
    <frame src="head.htm" name="head" marginwidth="0"
    marginheight="0" scrolling=no noresize>
    <frame src="home.htm" name="MainFrame" scrolling="yes"
    noresize="noresize" marginwidth="0" marginheight="0"
    id="MainFrame">
    <frame src="footer.htm" name="footer" marginwidth="0"
    marginheight="0" scrolling=no noresize>
    </frameset>
    <frame src="right.htm" name="right" marginwidth="0"
    marginheight="0" scrolling=no noresize>
    </frameset>
    <noframes><body>
    </body></noframes>
    </html>

    In the home.htm file that loads into your main frame, change
    the DOCTYPE.
    CHANGE:
    !DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Frameset//EN"
    http://www.w3.org/TR/xhtml1/DTD/xhtml1-frameset.dtd"
    TO THIS:
    <!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01
    Transitional//EN">BTW:
    "Bumbing" has no effect in the NNTP forums where most of the
    answers come
    from and it's just annoying to the web form user who are
    patiently waiting
    for a response.

  • I am not able to redeem my redemption code

    i purchased the adobe cloud because my upgrade to elements 12 never worked despite endless hours talking to would be experts, so i decided to lose the 67 gbp and try creative cloud for ligfhtroom 5 and photoshop cc however i am having the same problems and keep getting asked for a redemption code which i cannot find.
    as far as software goes adobe sucks and i am at the end of my patience after using your products for 9 years, if this problem is not resolved tonight then i will be cancelling my direct debit and moving over to a rival company like zonerama, who do not make it difficult for their customers to install their products and I will be reluctantly ending a 9 year period with elements,and i can assure you those 9 years were easy years for downloading software,the problem now is that in order to deter illegal use of your products you are making it difficult for your paying custoimers to use your products, maybe somebody from the upper management hierarchy has not been looking at the amount of complaints ( and generally al recurring ones at that) or if they have they are ignoring them at their peril, it seems by the amount of recurring problems of the same type that the experts are clutching at straws too, for the elements 12 problem i was directed deep into my computers system to no avail then was cut short

    Branching this to a separate discussion
    Akuj I am sorry you have been facing a difficult experience utilizing Elements 12, Photoshop CC, and Lightroom 5.  If you are facing difficulty redeeming your redemption code then please see Redemption Code Help.

  • How to redirect to an html page on submit

    I have this form and I would like when people click the submit btn, to be redirected to an html landing page. I'm not sure if I need to modify the php or the action script or both. Does anyone know how to do this?
    Thank you
    here is the code for both
    import flash.net.URLVariables; import flash.net.URLRequest;  /* Mouse Click Event Clicking on the specified symbol instance executes a function in which you can add your own custom code.  Instructions: 1. Add your custom code on a new line after the line that says "// Start your custom code" below. The code will execute when the symbol instance is clicked. */   submit.addEventListener(MouseEvent.CLICK, fl_MouseClickHandler);  function fl_MouseClickHandler(event:MouseEvent):void {            if (eMail.text == ""){           eMail.text = "Please enter in your email address";            }      else{           // Start your custom code      // create a variable container      var allVars:URLVariables = new URLVariables();      allVars.eMail = eMail.text;      allVars.bead = bead.selected;      allVars.jewelry = jewelry.selected;      allVars.onlineNewsletter = onlineNewsletter.selected;      allVars.sandiegoNewsletter = sandiegoNewsletter.selected;      //send info to URL      var mailAddress:URLRequest = new URLRequest("http://www.southsunbeads.com/media/flash/form.php");      mailAddress.data = allVars;      mailAddress.method = URLRequestMethod.POST;      sendToURL(mailAddress);           thankyou.text = "Thank you!";      }       eMail.text = "";         bead.selected = false;         jewelry.selected = false;         onlineNewsletter.selected = false;         sandiegoNewsletter.selected = false; }

    <?php
    // Create local variables from the Flash ActionScript posted variables
    $senderEmail     = $_POST['eMail'];
    $senderNewsletter1 = $_POST['bead'];
    $senderNewsletter2 = $_POST['jewelry'];
    $senderNewsletter3 = $_POST['onlineNewsletter'];
    $senderNewsletter4 = $_POST['sandiegoNewsletter'];
    // Strip slashes on the Local typed-in variables for security and run any php based error check here
    $senderEmail     = stripslashes($eMail);
    $senderMessage   = stripslashes($senderMessage);
    // IMPORTANT - Change these lines to be appropriate for your needs - IMPORTANT !!!!!!!!!!!!!!!!!!
    $to = "[email protected]";            
    $from = "$senderEmail";
    $subject = "Our customers from facebook and social networking";
    // Modify the Body of the message however you like
    $message = "Results from the form:
    eMail: $senderEmail
    Bead deal of the day: $senderNewsletter1
    Jewelry deal of the day: $senderNewsletter2
    online Newsletter: $senderNewsletter3
    San Diego Newsletter: $senderNewsletter4
    Their Message is below:
    $senderMessage";
    // Build $headers Variable
    $headers = "From: $from\r\n";
    $headers .= "Content-type: text\r\n";
    $to = "$to";
        // Send the email
        mail($to, $subject, $message, $headers);
        // Assemble the message that goes back to Flash
        // The flash ActionScript is looking for a return variable of "return_msg" there is no sendername in my form, can be just change to generic message
        $my_msg = "Thanks $senderName, all data has been sent.";
        // Print the data back to flash who is patiently waiting for it in the onCompleteHandler
        print "return_msg=$my_msg";
    // Exit script   
    exit();
    ?>
    import flash.net.URLVariables;
    import flash.net.URLRequest;
    /* Mouse Click Event
    Clicking on the specified symbol instance executes a function in which you can add your own custom code.
    Instructions:
    1. Add your custom code on a new line after the line that says "// Start your custom code" below.
    The code will execute when the symbol instance is clicked.
    submit.addEventListener(MouseEvent.CLICK, fl_MouseClickHandler);
    function fl_MouseClickHandler(event:MouseEvent):void
        if (eMail.text == ""){
            eMail.text = "Please enter in your email address";
        else{
            // Start your custom code
        // create a variable container
        var allVars:URLVariables = new URLVariables();
        allVars.eMail = eMail.text;
        allVars.bead = bead.selected;
        allVars.jewelry = jewelry.selected;
        allVars.onlineNewsletter = onlineNewsletter.selected;
        allVars.sandiegoNewsletter = sandiegoNewsletter.selected;
        //send info to URL
        var mailAddress:URLRequest = new URLRequest("http://www.southsunbeads.com/media/flash/form.php");
        mailAddress.data = allVars;
        mailAddress.method = URLRequestMethod.POST;
        sendToURL(mailAddress);
            thankyou.text = "Thank you!";
         eMail.text = "";
            bead.selected = false;
            jewelry.selected = false;
            onlineNewsletter.selected = false;
            sandiegoNewsletter.selected = false;

Maybe you are looking for

  • Driver can't communicate with new officejet pro 8610 for scanning

    I just bought a new officejet pro 8610.  Followed all directions and set up with wireless connection.  Prints fine but will not scan.  Will not work if used at control panel on printer or software.  First tried it on a windows 7 machine.  Just tried

  • Server side contacts removal

    Hello, As I have recently learned contacts added to Skype, including their personal data manually associated by the user, are stored permanently on the Skype servers. Even if the user removes the contact from his client the contact and its associated

  • Can't have multiple Web Service connections in SP1

    Hello, I'm currently interested in adding more than 1 Web Service connection to a particular xcelsius file, but after adding the first connection, the option is disabled in the Data Manager screen. Is there a workaround for this, since before service

  • Using dvd player with apple TV and airplay

    I am having problems to use the apple TV to see a DVD with the air play mode I tried to watch a movie using the default DVD player that comes with my iMac and when I activated air play to connect the iMac with the projector through the Apple TV, the

  • Installing illustrator on another computer

    I have Adobe Illustrator CS4 on my PC (which is no longer working). I have the disk and codes but I can't seem to install it on my laptop. How can I get it to work?