| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686 |
- &ANALYZE-SUSPEND _VERSION-NUMBER UIB_v8r12 GUI ADM1
- &ANALYZE-RESUME
- &Scoped-define WINDOW-NAME CURRENT-WINDOW
- &Scoped-define FRAME-NAME D-Dialog
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _DEFINITIONS D-Dialog
- /*------------------------------------------------------------------------
- File:
- Description: from cntnrdlg.w - ADM SmartDialog Template
- Input Parameters:
- <none>
- Output Parameters:
- <none>
- Author:
- Created:
- ------------------------------------------------------------------------*/
- /* This .W file was created with the Progress UIB. */
- /*----------------------------------------------------------------------*/
- /* Create an unnamed pool to store all the widgets created
- by this procedure. This is a good default which assures
- that this procedure's triggers and internal procedures
- will execute in this procedure's storage, and that proper
- cleanup will occur on deletion of the procedure. */
- CREATE WIDGET-POOL.
- /* *************************** Definitions ************************** */
- /* Parameters Definitions --- */
- /* Local Variable Definitions --- */
- DEF VAR ok AS LOG NO-UNDO.
- DEF VAR VHerst AS INT NO-UNDO.
- DEF VAR VWgr AS INT NO-UNDO.
- DEF VAR VBiercd AS INT NO-UNDO.
- DEF VAR VPreisgrp AS INT NO-UNDO.
- DEF VAR VDatum AS DATE NO-UNDO.
- DEF VAR BDatum AS DATE NO-UNDO.
- DEF TEMP-TABLE TWork FIELD Artnr AS INT
- FIELD Inhalt AS INT
- FIELD Jahr AS INT
- FIELD Eingang AS DEC DECIMALS 4
- FIELD EP AS DEC DECIMALS 4
- FIELD Ausgang AS DEC DECIMALS 4
- FIELD VP AS DEC DECIMALS 4
- FIELD RID AS RECID
- FIELD Art AS LOG
- FIELD Wert AS DEC DECIMALS 4.
- /* ---------- Globale Variablen ---------------------------------- */
- { v8/globvar.i" " " " "SHARED" }
- { v8/debivar.i " " " " "SHARED" }
- { v8/artivar.i " " " " "SHARED" }
- { v8/contvar.i " " " " "SHARED" }
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &ANALYZE-SUSPEND _UIB-PREPROCESSOR-BLOCK
- /* ******************** Preprocessor Definitions ******************** */
- &Scoped-define PROCEDURE-TYPE SmartDialog
- &Scoped-define DB-AWARE no
- &Scoped-define ADM-CONTAINER DIALOG-BOX
- /* Name of designated FRAME-NAME and/or first browse and/or first query */
- &Scoped-define FRAME-NAME D-Dialog
- /* Standard List Definitions */
- &Scoped-Define ENABLED-OBJECTS RECT-21 RECT-22 RECT-23 CB_Hersteller ~
- CB_Warengrp CB_Vertragsart CB_Preisgruppe F_VonDatum F_BisDatum Btn_Start ~
- Btn_Abbrechen
- &Scoped-Define DISPLAYED-OBJECTS CB_Hersteller CB_Warengrp CB_Vertragsart ~
- CB_Preisgruppe F_VonDatum F_BisDatum
- /* Custom List Definitions */
- /* List-1,List-2,List-3,List-4,List-5,List-6 */
- &Scoped-define List-1 CB_Hersteller CB_Warengrp CB_Vertragsart ~
- CB_Preisgruppe F_VonDatum F_BisDatum Btn_Start Btn_Abbrechen
- &Scoped-define List-6 CB_Hersteller CB_Warengrp CB_Vertragsart ~
- CB_Preisgruppe F_VonDatum F_BisDatum
- /* _UIB-PREPROCESSOR-BLOCK-END */
- &ANALYZE-RESUME
- /* *********************** Control Definitions ********************** */
- /* Define a dialog box */
- /* Definitions of the field level widgets */
- DEFINE BUTTON Btn_Abbrechen
- LABEL "&Abbrechen"
- SIZE 16 BY 1.
- DEFINE BUTTON Btn_Start
- LABEL "&Starten"
- SIZE 16 BY 1.
- DEFINE VARIABLE CB_Hersteller AS CHARACTER FORMAT "X(256)":U
- LABEL "Hersteller"
- VIEW-AS COMBO-BOX SORT INNER-LINES 5
- DROP-DOWN-LIST
- SIZE 40 BY 1
- BGCOLOR 15 NO-UNDO.
- DEFINE VARIABLE CB_Preisgruppe AS CHARACTER FORMAT "X(256)":U
- LABEL "Preisgruppe"
- VIEW-AS COMBO-BOX INNER-LINES 5
- DROP-DOWN-LIST
- SIZE 40 BY 1
- BGCOLOR 15 NO-UNDO.
- DEFINE VARIABLE CB_Vertragsart AS CHARACTER FORMAT "X(256)":U
- LABEL "Vertragsart"
- VIEW-AS COMBO-BOX INNER-LINES 5
- DROP-DOWN-LIST
- SIZE 40 BY 1
- BGCOLOR 15 NO-UNDO.
- DEFINE VARIABLE CB_Warengrp AS CHARACTER FORMAT "X(256)":U
- LABEL "Biergruppe"
- VIEW-AS COMBO-BOX INNER-LINES 5
- DROP-DOWN-LIST
- SIZE 40 BY 1
- BGCOLOR 15 NO-UNDO.
- DEFINE VARIABLE F_BisDatum AS DATE FORMAT "99.99.9999":U
- VIEW-AS FILL-IN NATIVE
- SIZE 16 BY 1
- BGCOLOR 15 NO-UNDO.
- DEFINE VARIABLE F_VonDatum AS DATE FORMAT "99.99.9999":U
- LABEL "von - bis Datum"
- VIEW-AS FILL-IN NATIVE
- SIZE 16 BY 1
- BGCOLOR 15 NO-UNDO.
- DEFINE RECTANGLE RECT-21
- EDGE-PIXELS 2 GRAPHIC-EDGE NO-FILL
- SIZE 86.8 BY 3.24.
- DEFINE RECTANGLE RECT-22
- EDGE-PIXELS 2 GRAPHIC-EDGE NO-FILL
- SIZE 86.8 BY 3.24.
- DEFINE RECTANGLE RECT-23
- EDGE-PIXELS 2 GRAPHIC-EDGE NO-FILL
- SIZE 86.8 BY 4.38.
- /* ************************ Frame Definitions *********************** */
- DEFINE FRAME D-Dialog
- CB_Hersteller AT ROW 2.05 COL 42 COLON-ALIGNED
- CB_Warengrp AT ROW 3.05 COL 42 COLON-ALIGNED
- CB_Vertragsart AT ROW 6.05 COL 42 COLON-ALIGNED
- CB_Preisgruppe AT ROW 7.1 COL 42 COLON-ALIGNED
- F_VonDatum AT ROW 9.86 COL 42 COLON-ALIGNED
- F_BisDatum AT ROW 9.86 COL 62 COLON-ALIGNED NO-LABEL
- Btn_Start AT ROW 11.57 COL 44
- Btn_Abbrechen AT ROW 11.57 COL 64
- "(alle ausser)" VIEW-AS TEXT
- SIZE 21.2 BY 1 AT ROW 7.05 COL 5.2
- "Kundenselektion" VIEW-AS TEXT
- SIZE 21.2 BY 1 AT ROW 6.05 COL 5.2
- "Artikelselektion" VIEW-AS TEXT
- SIZE 21.2 BY 1 AT ROW 2.05 COL 5.2
- RECT-21 AT ROW 1.48 COL 2.4
- RECT-22 AT ROW 5.48 COL 2.4
- RECT-23 AT ROW 9.05 COL 2.4
- SPACE(1.59) SKIP(0.46)
- WITH VIEW-AS DIALOG-BOX KEEP-TAB-ORDER
- SIDE-LABELS NO-UNDERLINE THREE-D SCROLLABLE
- TITLE "Kanalabrechung Feldschlösschen"
- DEFAULT-BUTTON Btn_Start CANCEL-BUTTON Btn_Abbrechen.
- /* *********************** Procedure Settings ************************ */
- &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
- /* Settings for THIS-PROCEDURE
- Type: SmartDialog
- Allow: Basic,Browse,DB-Fields,Query,Smart
- Other Settings: COMPILE
- */
- &ANALYZE-RESUME _END-PROCEDURE-SETTINGS
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB D-Dialog
- /* ************************* Included-Libraries *********************** */
- {src/adm/method/containr.i}
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- /* *********** Runtime Attributes and AppBuilder Settings *********** */
- &ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES
- /* SETTINGS FOR DIALOG-BOX D-Dialog
- FRAME-NAME */
- ASSIGN
- FRAME D-Dialog:SCROLLABLE = FALSE
- FRAME D-Dialog:HIDDEN = TRUE.
- /* SETTINGS FOR BUTTON Btn_Abbrechen IN FRAME D-Dialog
- 1 */
- /* SETTINGS FOR BUTTON Btn_Start IN FRAME D-Dialog
- 1 */
- /* SETTINGS FOR COMBO-BOX CB_Hersteller IN FRAME D-Dialog
- 1 6 */
- /* SETTINGS FOR COMBO-BOX CB_Preisgruppe IN FRAME D-Dialog
- 1 6 */
- /* SETTINGS FOR COMBO-BOX CB_Vertragsart IN FRAME D-Dialog
- 1 6 */
- /* SETTINGS FOR COMBO-BOX CB_Warengrp IN FRAME D-Dialog
- 1 6 */
- /* SETTINGS FOR FILL-IN F_BisDatum IN FRAME D-Dialog
- 1 6 */
- /* SETTINGS FOR FILL-IN F_VonDatum IN FRAME D-Dialog
- 1 6 */
- /* _RUN-TIME-ATTRIBUTES-END */
- &ANALYZE-RESUME
- /* Setting information for Queries and Browse Widgets fields */
- &ANALYZE-SUSPEND _QUERY-BLOCK DIALOG-BOX D-Dialog
- /* Query rebuild information for DIALOG-BOX D-Dialog
- _Options = "SHARE-LOCK"
- _Query is NOT OPENED
- */ /* DIALOG-BOX D-Dialog */
- &ANALYZE-RESUME
-
- /* ************************ Control Triggers ************************ */
- &Scoped-define SELF-NAME D-Dialog
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL D-Dialog D-Dialog
- ON WINDOW-CLOSE OF FRAME D-Dialog /* Kanalabrechung Feldschlösschen */
- DO:
- /* Add Trigger to equate WINDOW-CLOSE to END-ERROR. */
- APPLY "END-ERROR":U TO SELF.
- END.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &Scoped-define SELF-NAME Btn_Abbrechen
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL Btn_Abbrechen D-Dialog
- ON CHOOSE OF Btn_Abbrechen IN FRAME D-Dialog /* Abbrechen */
- DO:
- APPLY "END-ERROR":U TO FRAME {&FRAME-NAME}.
- END.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &Scoped-define SELF-NAME Btn_Start
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL Btn_Start D-Dialog
- ON CHOOSE OF Btn_Start IN FRAME D-Dialog /* Starten */
- DO:
- DO WITH FRAME {&FRAME-NAME}:
- ASSIGN {&List-6}.
- VHerst = INTEGER(SUBSTRING(CB_Hersteller :SCREEN-VALUE,01,03)).
- VWgr = INTEGER(SUBSTRING(CB_Warengrp :SCREEN-VALUE,01,03)).
- VBiercd = INTEGER(SUBSTRING(CB_Vertragsart:SCREEN-VALUE,01,03)).
- VPreisgrp = INTEGER(SUBSTRING(CB_Preisgruppe:SCREEN-VALUE,01,03)).
- IF F_VonDatum = ? THEN DO:
- APPLY 'ENTRY' TO F_VonDatum.
- RETURN NO-APPLY.
- END.
- IF F_BisDatum = ? THEN DO:
- APPLY 'ENTRY' TO F_BisDatum.
- RETURN NO-APPLY.
- END.
- IF F_BisDatum < F_VonDatum THEN DO:
- APPLY 'ENTRY' TO F_VonDatum.
- RETURN NO-APPLY.
- END.
- VDatum = F_VonDatum.
- BDatum = F_BisDatum.
- DISPLAY {&List-6}.
- RUN SCHREIBENFWAUSWERTUNGEN ( INPUT 'd-kanalabrechnung',
- INPUT FRAME {&FRAME-NAME}:CURRENT-ITERATION ) NO-ERROR.
- DISABLE {&List-1}.
- RUN BERECHNEN.
- ENABLE {&List-1}.
- END.
- END.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &UNDEFINE SELF-NAME
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK D-Dialog
- /* *************************** Main Block *************************** */
- CB_Hersteller:DELIMITER = ";".
- ok = TRUE.
- DO WHILE ok:
- ok = CB_Hersteller:DELETE(1).
- END.
- FOR EACH Tabel USE-INDEX Tabel-k2
- WHERE Tabel.Firma = GVFirma
- AND Tabel.RecArt = 'HERST' NO-LOCK:
- ok = CB_Hersteller:ADD-LAST(STRING(Tabel.CodeI,"999 ") + Tabel.Bez1).
- END.
- CB_Hersteller:SCREEN-VALUE = CB_Hersteller:ENTRY(1).
- CB_Warengrp:DELIMITER = ';'.
- ok = TRUE.
- DO WHILE ok:
- ok = CB_Warengrp:DELETE(1).
- END.
- FOR EACH WarenGrp USE-INDEX WarenGrp-k1
- WHERE WarenGrp.Firma = GVFirma NO-LOCK:
- ok = CB_Warengrp:ADD-LAST(STRING(WarenGrp.Wg,"999 ") + WarenGrp.Bez1).
- END.
- CB_Warengrp:SCREEN-VALUE = CB_Warengrp:ENTRY(1).
- CB_Vertragsart:DELIMITER = ";".
- ok = TRUE.
- DO WHILE ok:
- ok = CB_Vertragsart:DELETE(1).
- END.
- FOR EACH Tabel USE-INDEX Tabel-k2
- WHERE Tabel.Firma = GVFirma
- AND Tabel.RecArt = 'BIER' NO-LOCK:
- ok = CB_Vertragsart:ADD-LAST(STRING(Tabel.CodeI,"999 ") + Tabel.Bez1).
- END.
- CB_Vertragsart:SCREEN-VALUE = CB_Vertragsart:ENTRY(1).
- CB_Preisgruppe:DELIMITER = ";".
- ok = TRUE.
- DO WHILE ok:
- ok = CB_Preisgruppe:DELETE(1).
- END.
- FOR EACH Tabel USE-INDEX Tabel-k2
- WHERE Tabel.Firma = GVFirma
- AND Tabel.RecArt = 'PREGRP' NO-LOCK:
- ok = CB_Preisgruppe:ADD-LAST(STRING(Tabel.CodeI,"999 ") + Tabel.Bez1).
- END.
- CB_Preisgruppe:SCREEN-VALUE = CB_Preisgruppe:ENTRY(1).
- {src/adm/template/dialogmn.i}
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- /* ********************** Internal Procedures *********************** */
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-create-objects D-Dialog _ADM-CREATE-OBJECTS
- PROCEDURE adm-create-objects :
- /*------------------------------------------------------------------------------
- Purpose: Create handles for all SmartObjects used in this procedure.
- After SmartObjects are initialized, then SmartLinks are added.
- Parameters: <none>
- ------------------------------------------------------------------------------*/
- END PROCEDURE.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-row-available D-Dialog _ADM-ROW-AVAILABLE
- PROCEDURE adm-row-available :
- /*------------------------------------------------------------------------------
- Purpose: Dispatched to this procedure when the Record-
- Source has a new row available. This procedure
- tries to get the new row (or foriegn keys) from
- the Record-Source and process it.
- Parameters: <none>
- ------------------------------------------------------------------------------*/
- /* Define variables needed by this internal procedure. */
- {src/adm/template/row-head.i}
- /* Process the newly available records (i.e. display fields,
- open queries, and/or pass records on to any RECORD-TARGETS). */
- {src/adm/template/row-end.i}
- END PROCEDURE.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE BERECHNEN D-Dialog
- PROCEDURE BERECHNEN :
- /*------------------------------------------------------------------------------
- Purpose:
- Parameters: <none>
- Notes:
- ------------------------------------------------------------------------------*/
- DEF VAR VProz AS DEC DECIMALS 4 NO-UNDO.
- DEF VAR VBetr AS DEC DECIMALS 4 NO-UNDO.
- DEF VAR VBetrag AS DEC DECIMALS 4 NO-UNDO.
- DEF VAR cVorlage AS CHAR NO-UNDO.
- DEF VAR cDaten AS CHAR NO-UNDO.
- DEF VAR cDokument AS CHAR NO-UNDO.
- DEF VAR cDateiName AS CHAR NO-UNDO.
- DEF VAR Zelle AS CHAR NO-UNDO.
- DEF VAR excelAppl AS COM-HANDLE NO-UNDO.
- DEF VAR ja AS LOG NO-UNDO.
- EMPTY TEMP-TABLE TWork .
-
- FOR EACH Artst USE-INDEX Artst-k1
- WHERE Artst.Firma = GVFirma
- AND Artst.Aktiv = TRUE
- AND Artst.Herst = VHerst
- AND Artst.Wg_Grp = VWgr NO-LOCK,
- LAST ArtKanal USE-INDEX ArtKanal-k1
- WHERE ArtKanal.Firma = Artst.Firma
- AND ArtKanal.Artnr = Artst.Artnr
- AND ArtKanal.Inhalt = Artst.Inhalt
- AND ArtKanal.Jahr = Artst.Jahr
- AND ArtKanal.Preis_Grp = VPreisgrp
- AND ArtKanal.Ab_Datum <= VDatum NO-LOCK:
- CREATE TWork.
- ASSIGN TWork.Artnr = Artst.Artnr
- TWork.Inhalt = Artst.Inhalt
- TWork.Jahr = Artst.Jahr
- TWork.EP = Artst.Listen_EP
- TWork.RID = RECID(Artst)
- TWork.Art = ArtKanal.Art
- TWork.Wert = ArtKanal.Wert.
- END.
-
- FOR EACH TWork:
- FIND LAST Artbw USE-INDEX Artbw-k2
- WHERE Artbw.Firma = GVFirma
- AND Artbw.Artnr = TWork.Artnr
- AND Artbw.Inhalt = TWork.Inhalt
- AND Artbw.Jahr = TWork.Jahr
- AND Artbw.Datum <= BDatum
- AND Artbw.Aktion = FALSE
- AND Artbw.Tr_Art = 11 NO-LOCK NO-ERROR.
- IF AVAILABLE Artbw THEN TWork.EP = Artbw.Preis.
-
- FOR EACH Artbw USE-INDEX Artbw-k2
- WHERE Artbw.Firma = GVFirma
- AND Artbw.Artnr = TWork.Artnr
- AND Artbw.Inhalt = TWork.Inhalt
- AND Artbw.Jahr = TWork.Jahr
- AND Artbw.Datum >= VDatum
- AND Artbw.Datum <= BDatum
- AND Artbw.Tr_Art < 11 NO-LOCK:
- IF Artbw.Tr_Art = 01 THEN DO:
- FIND Debst NO-LOCK USE-INDEX Debst-k1
- WHERE Debst.Firma = Artbw.Firma
- AND Debst.Knr = Artbw.Knr NO-ERROR.
- IF Debst.Bier_Cd = VBiercd AND
- Debst.Preis_Grp = VPreisgrp THEN NEXT.
-
- TWork.Ausgang = TWork.Ausgang + Artbw.Menge.
- TWork.VP = TWork.VP + (Artbw.Menge * Artbw.Preis).
- NEXT.
- END.
- END.
- END.
- cVorlage = 'Kanal' + '.xls'.
- cDokument = 'Kanal' + '.xls'.
- cDaten = 'Kanal' + '.txt'.
- cDateiName = cDokument + CHR(01) + cVorlage.
- RUN CREATEDATEI ( INPUT cDateiName ).
- IF RETURN-VALUE BEGINS 'ERROR' THEN RETURN NO-APPLY.
- cDokument = RETURN-VALUE.
- RUN CREATEDATEI ( INPUT cDaten ).
- IF RETURN-VALUE BEGINS 'ERROR' THEN RETURN NO-APPLY.
- cDaten = RETURN-VALUE.
- OUTPUT TO VALUE(cDaten).
- VBetrag = 0.
- FOR EACH TWork WHERE Ausgang <> 0:
- FIND Artst WHERE RECID(Artst) = TWork.RID NO-LOCK.
- FIND KGebind WHERE KGebinde.Firma = "1000"
- AND KGebinde.Geb_Cd = Artst.KGeb_Cd.
- IF TWork.Art = TRUE THEN DO:
- VProz = TWork.Wert.
- VBetr = TWork.EP * VProz / 100.
- END.
- ELSE DO:
- VBetr = TWork.Wert.
- VProz = VBetr * 100 / TWork.EP.
- END.
- Rundbetr = TWork.Ausgang * VBetr.
-
- PUT CONTROL '£'
- Artst.Bez '£'
- KGebinde.KBez '£'
- TRIM(STRING(VProz ,'z9.99')) '£'
- TRIM(STRING(TWork.Ausgang,'->>>,>>>,>>9')) '£'
- TRIM(STRING(TWork.EP ,'->>>,>>>,>>9.99')) '£'
- TRIM(STRING(VBetr ,'->>>,>>>,>>9.99')) '£'
- TRIM(STRING(Rundbetr ,'->>>,>>>,>>9.99')) CHR(10).
- VBetrag = VBetrag + Rundbetr.
- END.
- PUT CONTROL '£££££££'
- TRIM(STRING(VBetrag,'->>>,>>>,>>9.99')) CHR(10).
-
- OUTPUT CLOSE.
- excelAppl = DYNAMIC-FUNCTION('CREATEEXCEL':U) NO-ERROR.
- IF NOT VALID-HANDLE(excelAppl) THEN DO:
- RUN FEHLER ( INPUT 1035 ).
- RETURN.
- END.
- RUN OPENEXCEL ( INPUT excelAppl, INPUT cDokument, INPUT '', OUTPUT ja ).
- IF NOT ja THEN DO:
- RUN FEHLER ( INPUT 1040 ).
- DYNAMIC-FUNCTION('RELEASEEXCEL':U, INPUT excelAppl ) NO-ERROR.
- RETURN NO-APPLY.
- END.
- Zelle = 'A5'.
- excelAppl:Range(Zelle):SELECT.
- excelAppl:SELECTION:FormulaR1C1 = 'TEXT;' + cDaten.
- excelAppl:APPLICATION:RUN ( 'DateiEinfügen' ).
- RUN KOPF ( INPUT excelAppl ).
- Zelle = 'A1'.
- excelAppl:Range(Zelle):SELECT.
- excelAppl:SELECTION:ColumnWidth = 0.3.
- DYNAMIC-FUNCTION('RELEASEEXCEL':U, INPUT excelAppl ) NO-ERROR.
- APPLY 'CHOOSE' TO Btn_Abbrechen IN FRAME {&FRAME-NAME}.
-
- END PROCEDURE.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI D-Dialog _DEFAULT-DISABLE
- PROCEDURE disable_UI :
- /*------------------------------------------------------------------------------
- Purpose: DISABLE the User Interface
- Parameters: <none>
- Notes: Here we clean-up the user-interface by deleting
- dynamic widgets we have created and/or hide
- frames. This procedure is usually called when
- we are ready to "clean-up" after running.
- ------------------------------------------------------------------------------*/
- /* Hide all frames. */
- HIDE FRAME D-Dialog.
- END PROCEDURE.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE enable_UI D-Dialog _DEFAULT-ENABLE
- PROCEDURE enable_UI :
- /*------------------------------------------------------------------------------
- Purpose: ENABLE the User Interface
- Parameters: <none>
- Notes: Here we display/view/enable the widgets in the
- user-interface. In addition, OPEN all queries
- associated with each FRAME and BROWSE.
- These statements here are based on the "Other
- Settings" section of the widget Property Sheets.
- ------------------------------------------------------------------------------*/
- DISPLAY CB_Hersteller CB_Warengrp CB_Vertragsart CB_Preisgruppe F_VonDatum
- F_BisDatum
- WITH FRAME D-Dialog.
- ENABLE RECT-21 RECT-22 RECT-23 CB_Hersteller CB_Warengrp CB_Vertragsart
- CB_Preisgruppe F_VonDatum F_BisDatum Btn_Start Btn_Abbrechen
- WITH FRAME D-Dialog.
- VIEW FRAME D-Dialog.
- {&OPEN-BROWSERS-IN-QUERY-D-Dialog}
- END PROCEDURE.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE KOPF D-Dialog
- PROCEDURE KOPF :
- /*------------------------------------------------------------------------------
- Purpose:
- Parameters: <none>
- Notes:
- ------------------------------------------------------------------------------*/
- DEF INPUT PARAMETER excelAppl AS COM-HANDLE NO-UNDO.
- DEF VAR cString AS CHAR NO-UNDO.
- cString = 'Abrechnungsperiode '
- + STRING(F_VonDatum,'99.99.9999')
- + ' bis '
- + STRING(F_BisDatum,'99.99.9999').
- RUN ZELLEFUELLEN ( INPUT excelAppl, INPUT 'H', INPUT 1, INPUT cString ).
- END PROCEDURE.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE local-view D-Dialog
- PROCEDURE local-view :
- /*------------------------------------------------------------------------------
- Purpose: Override standard ADM method
- Notes:
- ------------------------------------------------------------------------------*/
- RUN dispatch IN THIS-PROCEDURE ( INPUT 'view':U ) .
- RUN LESENFWAUSWERTUNGEN ( INPUT 'd-kanalabrechnung',
- INPUT FRAME {&FRAME-NAME}:CURRENT-ITERATION ) NO-ERROR.
- END PROCEDURE.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-records D-Dialog _ADM-SEND-RECORDS
- PROCEDURE send-records :
- /*------------------------------------------------------------------------------
- Purpose: Send record ROWID's for all tables used by
- this file.
- Parameters: see template/snd-head.i
- ------------------------------------------------------------------------------*/
- /* SEND-RECORDS does nothing because there are no External
- Tables specified for this SmartDialog, and there are no
- tables specified in any contained Browse, Query, or Frame. */
- END PROCEDURE.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE state-changed D-Dialog
- PROCEDURE state-changed :
- /* -----------------------------------------------------------
- Purpose:
- Parameters: <none>
- Notes:
- -------------------------------------------------------------*/
- DEFINE INPUT PARAMETER p-issuer-hdl AS HANDLE NO-UNDO.
- DEFINE INPUT PARAMETER p-state AS CHARACTER NO-UNDO.
- END PROCEDURE.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
|