&ANALYZE-SUSPEND _VERSION-NUMBER AB_v10r12 GUI ADM2 &ANALYZE-RESUME &Scoped-define WINDOW-NAME CURRENT-WINDOW &Scoped-define FRAME-NAME gGebindeRechnung {adecomm/appserv.i} &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _DEFINITIONS gGebindeRechnung /*------------------------------------------------------------------------ File: Description: from cntnrdlg.w - ADM2 SmartDialog Template Input Parameters: Output Parameters: Author: Created: ------------------------------------------------------------------------*/ /* This .W file was created with the Progress AppBuilder. */ /*----------------------------------------------------------------------*/ /* 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 --- */ DEF INPUT PARAMETER ipAufnr AS INT NO-UNDO. /* Local Variable Definitions --- */ DEF VAR iKnr AS INT NO-UNDO. DEF VAR iAufnr AS INT NO-UNDO. DEF VAR iFakart AS INT NO-UNDO. DEF VAR iArtnr AS INT NO-UNDO. DEF BUFFER bAufko FOR Aufko. DEF BUFFER bDebst FOR Debst. DEF BUFFER lDebst FOR Debst. DEF BUFFER bArtst FOR Artst. DEF BUFFER bAdresse FOR Adresse. DEF TEMP-TABLE tAufze LIKE Aufze. DEF TEMP-TABLE xAufze LIKE Aufze. { incl/dlgdefinition.i } { src/adm2/widgetprto.i } /* _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 &Scoped-define ADM-SUPPORTED-LINKS Data-Target,Data-Source,Page-Target,Update-Source,Update-Target /* Name of designated FRAME-NAME and/or first browse and/or first query */ &Scoped-define FRAME-NAME gGebindeRechnung /* Standard List Definitions */ &Scoped-Define ENABLED-OBJECTS RECT-2 F_Aufnr F_Knr F_Kunde CB_Fakart ~ F_vondatum F_bisdatum F_Artnr F_Artikel Btn_OK Btn_Cancel &Scoped-Define DISPLAYED-OBJECTS F_Aufnr F_Knr F_Kunde CB_Fakart F_vondatum ~ F_bisdatum F_Artnr F_Artikel /* Custom List Definitions */ /* List-1,List-2,List-3,List-4,List-5,List-6 */ &Scoped-define List-6 F_Aufnr F_Knr F_Kunde F_vondatum F_bisdatum F_Artnr ~ F_Artikel /* _UIB-PREPROCESSOR-BLOCK-END */ &ANALYZE-RESUME /* ************************ Function Prototypes ********************** */ &ANALYZE-SUSPEND _UIB-CODE-BLOCK _FUNCTION-FORWARD validateArtnr gGebindeRechnung FUNCTION validateArtnr RETURNS LOGICAL ( /* parameter-definitions */ ) FORWARD. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME /* *********************** Control Definitions ********************** */ /* Define a dialog box */ /* Definitions of the field level widgets */ DEFINE BUTTON Btn_Cancel AUTO-END-KEY LABEL "abbrechen" SIZE 15 BY 1. DEFINE BUTTON Btn_OK AUTO-GO LABEL "OK" SIZE 15 BY 1. DEFINE VARIABLE CB_Fakart AS CHARACTER FORMAT "X(256)":U LABEL "Fakturaart" VIEW-AS COMBO-BOX INNER-LINES 5 LIST-ITEM-PAIRS "Item 1","Item 1" DROP-DOWN-LIST SIZE 50 BY 1 NO-UNDO. DEFINE VARIABLE F_Artikel AS CHARACTER FORMAT "X(256)":U LABEL "/" VIEW-AS FILL-IN NATIVE SIZE 80 BY 1 BGCOLOR 15 NO-UNDO. DEFINE VARIABLE F_Artnr AS INTEGER FORMAT "zzzzzz9":U INITIAL 0 LABEL "Artikel" VIEW-AS FILL-IN NATIVE SIZE 12 BY 1 BGCOLOR 15 NO-UNDO. DEFINE VARIABLE F_Aufnr AS INTEGER FORMAT "zzzzzz9":U INITIAL 0 LABEL "Auftrag" VIEW-AS FILL-IN NATIVE SIZE 12 BY 1 BGCOLOR 15 NO-UNDO. DEFINE VARIABLE F_bisdatum AS DATE FORMAT "99.99.9999":U INITIAL 01/01/20 LABEL "/" VIEW-AS FILL-IN NATIVE SIZE 16 BY 1 BGCOLOR 15 NO-UNDO. DEFINE VARIABLE F_Knr AS INTEGER FORMAT "zzzzzz9":U INITIAL 0 LABEL "Kunde" VIEW-AS FILL-IN NATIVE SIZE 12 BY 1 BGCOLOR 15 NO-UNDO. DEFINE VARIABLE F_Kunde AS CHARACTER FORMAT "X(256)":U LABEL "/" VIEW-AS FILL-IN NATIVE SIZE 80 BY 1 BGCOLOR 15 NO-UNDO. DEFINE VARIABLE F_vondatum AS DATE FORMAT "99.99.9999":U INITIAL 01/01/20 LABEL "von - bis Datum" VIEW-AS FILL-IN NATIVE SIZE 16 BY 1 BGCOLOR 15 NO-UNDO. DEFINE RECTANGLE RECT-2 EDGE-PIXELS 2 GRAPHIC-EDGE NO-FILL SIZE 114 BY 6.67. /* ************************ Frame Definitions *********************** */ DEFINE FRAME gGebindeRechnung F_Aufnr AT ROW 2 COL 18 COLON-ALIGNED WIDGET-ID 4 NO-TAB-STOP F_Knr AT ROW 3 COL 18 COLON-ALIGNED WIDGET-ID 6 NO-TAB-STOP F_Kunde AT ROW 3 COL 33 COLON-ALIGNED WIDGET-ID 8 NO-TAB-STOP CB_Fakart AT ROW 4 COL 18 COLON-ALIGNED WIDGET-ID 10 F_vondatum AT ROW 5 COL 18 COLON-ALIGNED WIDGET-ID 12 F_bisdatum AT ROW 5 COL 37 COLON-ALIGNED WIDGET-ID 14 F_Artnr AT ROW 6 COL 18 COLON-ALIGNED WIDGET-ID 18 F_Artikel AT ROW 6 COL 33 COLON-ALIGNED WIDGET-ID 20 NO-TAB-STOP Btn_OK AT ROW 9 COL 40.6 Btn_Cancel AT ROW 9 COL 61.8 RECT-2 AT ROW 1.48 COL 3 WIDGET-ID 2 SPACE(2.19) SKIP(3.13) WITH VIEW-AS DIALOG-BOX KEEP-TAB-ORDER SIDE-LABELS NO-UNDERLINE THREE-D SCROLLABLE TITLE "Gebinderechnung" CANCEL-BUTTON Btn_Cancel WIDGET-ID 100. /* *********************** Procedure Settings ************************ */ &ANALYZE-SUSPEND _PROCEDURE-SETTINGS /* Settings for THIS-PROCEDURE Type: SmartDialog Allow: Basic,Browse,DB-Fields,Query,Smart Container Links: Data-Target,Data-Source,Page-Target,Update-Source,Update-Target Design Page: 1 Other Settings: COMPILE APPSERVER */ &ANALYZE-RESUME _END-PROCEDURE-SETTINGS &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB gGebindeRechnung /* ************************* Included-Libraries *********************** */ {src/adm2/containr.i} /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME /* *********** Runtime Attributes and AppBuilder Settings *********** */ &ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES /* SETTINGS FOR DIALOG-BOX gGebindeRechnung FRAME-NAME */ ASSIGN FRAME gGebindeRechnung:SCROLLABLE = FALSE FRAME gGebindeRechnung:HIDDEN = TRUE. /* SETTINGS FOR FILL-IN F_Artikel IN FRAME gGebindeRechnung 6 */ ASSIGN F_Artikel:READ-ONLY IN FRAME gGebindeRechnung = TRUE. /* SETTINGS FOR FILL-IN F_Artnr IN FRAME gGebindeRechnung 6 */ /* SETTINGS FOR FILL-IN F_Aufnr IN FRAME gGebindeRechnung 6 */ ASSIGN F_Aufnr:READ-ONLY IN FRAME gGebindeRechnung = TRUE. /* SETTINGS FOR FILL-IN F_bisdatum IN FRAME gGebindeRechnung 6 */ /* SETTINGS FOR FILL-IN F_Knr IN FRAME gGebindeRechnung 6 */ ASSIGN F_Knr:READ-ONLY IN FRAME gGebindeRechnung = TRUE. /* SETTINGS FOR FILL-IN F_Kunde IN FRAME gGebindeRechnung 6 */ ASSIGN F_Kunde:READ-ONLY IN FRAME gGebindeRechnung = TRUE. /* SETTINGS FOR FILL-IN F_vondatum IN FRAME gGebindeRechnung 6 */ /* _RUN-TIME-ATTRIBUTES-END */ &ANALYZE-RESUME /* Setting information for Queries and Browse Widgets fields */ &ANALYZE-SUSPEND _QUERY-BLOCK DIALOG-BOX gGebindeRechnung /* Query rebuild information for DIALOG-BOX gGebindeRechnung _Options = "SHARE-LOCK" _Query is NOT OPENED */ /* DIALOG-BOX gGebindeRechnung */ &ANALYZE-RESUME /* ************************ Control Triggers ************************ */ &Scoped-define SELF-NAME gGebindeRechnung &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL gGebindeRechnung gGebindeRechnung ON END-ERROR OF FRAME gGebindeRechnung /* Gebinderechnung */ DO: RUN ENDE. RETURN NO-APPLY. END. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL gGebindeRechnung gGebindeRechnung ON WINDOW-CLOSE OF FRAME gGebindeRechnung /* Gebinderechnung */ DO: RUN ENDE. RETURN NO-APPLY. END. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME &Scoped-define SELF-NAME Btn_Cancel &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL Btn_Cancel gGebindeRechnung ON CHOOSE OF Btn_Cancel IN FRAME gGebindeRechnung /* abbrechen */ DO: RUN ENDE. RETURN NO-APPLY. END. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME &Scoped-define SELF-NAME Btn_OK &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL Btn_OK gGebindeRechnung ON CHOOSE OF Btn_OK IN FRAME gGebindeRechnung /* OK */ DO: btnOK = TRUE. Btn_OK :SENSITIVE = FALSE. Btn_Cancel:SENSITIVE = FALSE. SESSION:SET-WAIT-STATE('GENERAL'). RUN GEBINDERECHNUNG. Btn_OK :SENSITIVE = TRUE. Btn_Cancel:SENSITIVE = TRUE. SESSION:SET-WAIT-STATE(''). IF RETURN-VALUE = 'ERROR' THEN RETURN NO-APPLY. RUN ENDE. RETURN NO-APPLY. END. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME &Scoped-define SELF-NAME F_Artnr &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL F_Artnr gGebindeRechnung ON ALT-F OF F_Artnr IN FRAME gGebindeRechnung /* Artikel */ DO: DEF VAR iRecid AS RECID NO-UNDO. RUN g-suchen-artikel.w ( '', OUTPUT iRecid) NO-ERROR. IF iRecid = ? OR iRecid = 0 THEN RETURN NO-APPLY. FIND Artst NO-LOCK WHERE RECID(Artst) = iRecid NO-ERROR. iArtnr = Artst.Artnr. F_Artnr = Artst.Artnr. F_Artikel = Artst.Bez. DO WITH FRAME {&FRAME-NAME}: DISPLAY F_Artnr F_Artikel. END. END. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL F_Artnr gGebindeRechnung ON LEAVE OF F_Artnr IN FRAME gGebindeRechnung /* Artikel */ DO: iArtnr = INTEGER(SELF:SCREEN-VALUE). IF DYNAMIC-FUNCTION('validateArtnr':U ) THEN RETURN. APPLY 'ENTRY' TO SELF. RETURN NO-APPLY. END. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME &UNDEFINE SELF-NAME &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK gGebindeRechnung /* *************************** Main Block *************************** */ { incl/dlgmainblock.i } {src/adm2/dialogmn.i} /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME /* ********************** Internal Procedures *********************** */ &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-create-objects gGebindeRechnung _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: ------------------------------------------------------------------------------*/ END PROCEDURE. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE disable_UI gGebindeRechnung _DEFAULT-DISABLE PROCEDURE disable_UI : /*------------------------------------------------------------------------------ Purpose: DISABLE the User Interface Parameters: 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 gGebindeRechnung. END PROCEDURE. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE enableObject gGebindeRechnung PROCEDURE enableObject : /*------------------------------------------------------------------------------ Purpose: Super Override Parameters: Notes: ------------------------------------------------------------------------------*/ FIND bAufko NO-LOCK WHERE bAufko.Firma = Firma AND bAufko.Aufnr = ipAufnr NO-ERROR. IF NOT AVAILABLE bAufko THEN DO: RUN ENDE. RETURN NO-APPLY. END. FIND bDebst NO-LOCK WHERE bDebst.Firma = bAufko.Firma AND bDebst.Knr = bAufko.Fak_Knr NO-ERROR. IF NOT AVAILABLE bDebst THEN DO: RUN ENDE. RETURN NO-APPLY. END. FIND lDebst NO-LOCK WHERE lDebst.Firma = bAufko.Firma AND lDebst.Knr = bAufko.Knr NO-ERROR. IF NOT AVAILABLE lDebst THEN DO: RUN ENDE. RETURN NO-APPLY. END. FIND bAdresse NO-LOCK WHERE bAdresse.Firma = AdFirma AND bAdresse.Knr = lDebst.Knr NO-ERROR. IF NOT AVAILABLE bAdresse THEN DO: RUN ENDE. RETURN NO-APPLY. END. ASSIGN F_Aufnr = bAufko.Aufnr F_Knr = lDebst.Knr F_Kunde = bAdresse.Anzeig_Br iKnr = lDebst.Knr iAufnr = bAufko.Aufnr. DO WITH FRAME {&FRAME-NAME}: RUN COMBO_FAKART ( CB_Fakart:HANDLE ). iFakart = DYNAMIC-FUNCTION('getGebRgFakart':U, F_Knr ) NO-ERROR. CB_Fakart:SCREEN-VALUE = STRING(iFakart,'999999') NO-ERROR. IF ERROR-STATUS:ERROR THEN DO: CB_Fakart:SCREEN-VALUE = ENTRY(2, CB_Fakart:LIST-ITEM-PAIRS, ';'). END. iArtnr = DYNAMIC-FUNCTION('getGebRgArtnr':U, F_Knr ) NO-ERROR. FIND bArtst NO-LOCK WHERE bArtst.Firma = Firma AND bArtst.Artnr = iArtnr AND bArtst.Inhalt = 0 AND bArtst.Jahr = 0 NO-ERROR. IF AVAILABLE bArtst THEN ASSIGN F_Artnr = bArtst.Artnr F_Artikel = bArtst.Bez. FIND LAST GebKontr NO-LOCK USE-INDEX GebKontr-k3 WHERE GebKontr.Firma = Firma AND GebKontr.Knr = iKnr AND GebKontr.lAbgerechnet NO-ERROR. F_vondatum = (IF AVAILABLE GebKontr THEN GebKontr.Datum + 1 ELSE DATE(MONTH(TODAY),01,YEAR(TODAY))). F_bisdatum = F_vondatum. DO WHILE TRUE: IF MONTH(F_bisdatum + 1) <> MONTH(F_bisdatum) THEN LEAVE. F_bisdatum = F_bisdatum + 1. END. END. { incl/dlgenableobject.i } END PROCEDURE. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE enable_UI gGebindeRechnung _DEFAULT-ENABLE PROCEDURE enable_UI : /*------------------------------------------------------------------------------ Purpose: ENABLE the User Interface Parameters: 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 F_Aufnr F_Knr F_Kunde CB_Fakart F_vondatum F_bisdatum F_Artnr F_Artikel WITH FRAME gGebindeRechnung. ENABLE RECT-2 F_Aufnr F_Knr F_Kunde CB_Fakart F_vondatum F_bisdatum F_Artnr F_Artikel Btn_OK Btn_Cancel WITH FRAME gGebindeRechnung. VIEW FRAME gGebindeRechnung. {&OPEN-BROWSERS-IN-QUERY-gGebindeRechnung} END PROCEDURE. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE ENDE gGebindeRechnung PROCEDURE ENDE : /*------------------------------------------------------------------------------ Purpose: Parameters: Notes: ------------------------------------------------------------------------------*/ IF btnOK THEN DO: END. { incl/dlgende.i } END PROCEDURE. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE GEBINDERECHNUNG gGebindeRechnung PROCEDURE GEBINDERECHNUNG : /*------------------------------------------------------------------------------ Purpose: Parameters: Notes: ------------------------------------------------------------------------------*/ DEF VAR htAufze AS HANDLE NO-UNDO. DEF VAR iRetVal AS INT NO-UNDO. DEF VAR lRetVal AS INT NO-UNDO. DEF VAR iPos AS INT NO-UNDO. DEF VAR nTotale AS DEC EXTENT 15 NO-UNDO. DEF VAR iRecid AS RECID NO-UNDO. DEF VAR lOK AS LOG INIT FALSE NO-UNDO. DEF BUFFER bArtst FOR Artst. DEF BUFFER bAufko FOR Aufko. DO WITH FRAME {&FRAME-NAME}: ASSIGN {&List-6}. iFakart = INTEGER(CB_Fakart:SCREEN-VALUE) NO-ERROR. iArtnr = F_Artnr. IF NOT DYNAMIC-FUNCTION('validateArtnr':U) THEN DO: APPLY 'ENTRY' TO F_Artnr. RETURN 'ERROR'. END. DYNAMIC-FUNCTION('setGebRgFakart':U, iKnr, iFakart ) NO-ERROR. DYNAMIC-FUNCTION('setGebRgArtnr':U , iKnr, iArtnr ) NO-ERROR. END. EMPTY TEMP-TABLE xAufze. htAufze = TEMP-TABLE tAufze:DEFAULT-BUFFER-HANDLE. FIND LAST Aufze NO-LOCK WHERE Aufze.Firma = Firma AND Aufze.Aufnr = iAufnr NO-ERROR. iPos = (IF NOT AVAILABLE Aufze THEN 5 ELSE Aufze.Pos + 5). CREATE xAufze. ASSIGN xAufze.Firma = Firma xAufze.Aufnr = iAufnr xAufze.Artnr = 0 xAufze.Inhalt = 0 xAufze.Jahr = 0 xAufze.Pos = iPos xAufze.Bez1 = '' xAufze.Bez2 = ''. iPos = iPos + 5. CREATE xAufze. ASSIGN xAufze.Firma = Firma xAufze.Aufnr = iAufnr xAufze.Artnr = 0 xAufze.Inhalt = 0 xAufze.Jahr = 0 xAufze.Pos = iPos xAufze.Bez1 = 'Gebindeabrechnung für die Periode' xAufze.Bez2 = SUBSTITUTE('vom &1 bis &2', STRING(F_vondatum,'99.99.9999'), STRING(F_bisdatum,'99.99.9999') ). iPos = iPos + 5. CREATE xAufze. ASSIGN xAufze.Firma = Firma xAufze.Aufnr = iAufnr xAufze.Artnr = 0 xAufze.Inhalt = 0 xAufze.Jahr = 0 xAufze.Pos = iPos xAufze.Bez1 = '' xAufze.Bez2 = '' . REPEAT TRANSACTION ON ERROR UNDO, LEAVE: FIND bAufko WHERE bAufko.Firma = Firma AND bAufko.Aufnr = iAufnr. ASSIGN bAufko.Fak_Art = iFakart bAufko.Samm_Nr = 0. FIND bArtst NO-LOCK WHERE bArtst.Firma = Firma AND bArtst.Artnr = iArtnr AND bArtst.Inhalt = 0 AND bArtst.Jahr = 0 NO-ERROR. FOR EACH GebKontr NO-LOCK USE-INDEX GebKontr-k3 WHERE GebKontr.Firma = Firma AND GebKontr.Knr = iKnr AND GebKontr.lAbgerechnet = FALSE AND GebKontr.Datum >= F_vondatum AND GebKontr.Datum <= F_bisdatum BREAK BY GebKontr.DokNr BY GebKontr.Geb_Cd : FIND GebKonto NO-LOCK WHERE GebKonto.Firma = Firma AND GebKonto.Geb_Cd = GebKontr.Geb_Cd NO-ERROR. IF FIRST-OF ( GebKontr.Doknr ) THEN DO: iPos = iPos + 5. CREATE xAufze. ASSIGN xAufze.Firma = Firma xAufze.Aufnr = iAufnr xAufze.Artnr = 0 xAufze.Inhalt = 0 xAufze.Jahr = 0 xAufze.Pos = iPos xAufze.Bez1 = SUBSTITUTE('Gebindeabrechnung aus Rechnung &1', TRIM(STRING(GebKontr.Doknr,'>>>>>>>9')) ) xAufze.Bez2 = ''. END. IF GebKontr.Ausgang <> 0 THEN DO: iPos = iPos + 5. EMPTY TEMP-TABLE tAufze. CREATE tAufze. ASSIGN tAufze.Firma = Firma tAufze.Aufnr = iAufnr tAufze.Artnr = iArtnr tAufze.Inhalt = 0 tAufze.Jahr = 0 tAufze.Pos = iPos . iRetVal = DYNAMIC-FUNCTION('fillAufze':U, INPUT-OUTPUT htAufze) NO-ERROR. IF iRetVal <> 0 THEN DO: MESSAGE iRetVal VIEW-AS ALERT-BOX INFORMATION BUTTONS OK. RETURN 'ERROR'. END. FIND FIRST tAufze. ASSIGN tAufze.Bez1 = GebKonto.Bez tAufze.Preis = GebKontr.Preis tAufze.PreisArt = 01 tAufze.KGeb_Be = GebKontr.Ausgang tAufze.KGeb_Me = GebKontr.Ausgang tAufze.MBest = GebKontr.Ausgang tAufze.MGeli = GebKontr.Ausgang . lRetVal = DYNAMIC-FUNCTION('calculateZeilenTotal':U, INPUT-OUTPUT htAufze) NO-ERROR. CREATE xAufze. BUFFER-COPY tAufze TO xAufze. END. IF GebKontr.Eingang <> 0 THEN DO: iPos = iPos + 5. EMPTY TEMP-TABLE tAufze. CREATE tAufze. ASSIGN tAufze.Firma = Firma tAufze.Aufnr = iAufnr tAufze.Artnr = iArtnr tAufze.Inhalt = 0 tAufze.Jahr = 0 tAufze.Pos = iPos . iRetVal = DYNAMIC-FUNCTION('fillAufze':U, INPUT-OUTPUT htAufze) NO-ERROR. IF iRetVal <> 0 THEN DO: MESSAGE iRetVal VIEW-AS ALERT-BOX INFORMATION BUTTONS OK. RETURN 'ERROR'. END. FIND FIRST tAufze. ASSIGN tAufze.Bez1 = GebKonto.Bez tAufze.Preis = GebKontr.Preis tAufze.PreisArt = 01 tAufze.KGeb_Be = - GebKontr.Eingang tAufze.KGeb_Me = - GebKontr.Eingang tAufze.MBest = - GebKontr.Eingang tAufze.MGeli = - GebKontr.Eingang . lRetVal = DYNAMIC-FUNCTION('calculateZeilenTotal':U, INPUT-OUTPUT htAufze) NO-ERROR. CREATE xAufze. BUFFER-COPY tAufze TO xAufze. END. IF LAST-OF ( GebKontr.Doknr ) THEN DO: iPos = iPos + 5. CREATE xAufze. ASSIGN xAufze.Firma = Firma xAufze.Aufnr = iAufnr xAufze.Artnr = 0 xAufze.Inhalt = 0 xAufze.Jahr = 0 xAufze.Pos = iPos xAufze.Bez1 = '' xAufze.Bez2 = ''. END. END. FOR EACH xAufze: CREATE Aufze. BUFFER-COPY xAufze TO Aufze. END. iRecid = RECID(bAufko). RELEASE bAufko. DYNAMIC-FUNCTION('calculateAuftragsTotal':U, Firma, iAufnr, OUTPUT nTotale ) NO-ERROR. PUBLISH 'reopenAufko' ( iRecid ). PUBLISH 'refreshAufko'. PUBLISH 'reopenAufze' ( 0 ). lOk = TRUE. LEAVE. END. IF lOK THEN DO: REPEAT TRANSACTION: FOR EACH GebKontr USE-INDEX GebKontr-k3 WHERE GebKontr.Firma = Firma AND GebKontr.Knr = iKnr AND GebKontr.lAbgerechnet = FALSE AND GebKontr.Datum >= F_vondatum AND GebKontr.Datum <= F_bisdatum : GebKontr.lAbgerechnet = TRUE. END. RELEASE GebKontr. LEAVE. END. END. END PROCEDURE. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME /* ************************ Function Implementations ***************** */ &ANALYZE-SUSPEND _UIB-CODE-BLOCK _FUNCTION validateArtnr gGebindeRechnung FUNCTION validateArtnr RETURNS LOGICAL ( /* parameter-definitions */ ) : /*------------------------------------------------------------------------------ Purpose: Notes: ------------------------------------------------------------------------------*/ DEF BUFFER bArtst FOR Artst. FIND bArtst NO-LOCK WHERE bArtst.Firma = Firma AND bArtst.Artnr = iArtnr AND bArtst.Inhalt = 0 AND bArtst.Jahr = 0 NO-ERROR. IF NOT AVAILABLE bArtst THEN RETURN FALSE. F_Artikel:SCREEN-VALUE IN FRAME {&FRAME-NAME} = bArtst.Bez. RETURN TRUE. END FUNCTION. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME