| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515 |
- &ANALYZE-SUSPEND _VERSION-NUMBER UIB_v8r12 GUI ADM1
- &ANALYZE-RESUME
- /* Connected Databases
- anadat PROGRESS
- */
- &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 VBez AS CHAR NO-UNDO.
- DEF VAR VInhalt AS INT NO-UNDO.
- DEF VAR VKGebinde AS CHAR NO-UNDO.
- DEF VAR VVGebinde AS CHAR NO-UNDO.
- DEF VAR VAlk_Gehalt AS DEC NO-UNDO.
- DEF VAR VDaten AS CHAR NO-UNDO.
- DEF VAR iLager AS INT NO-UNDO.
- DEF VAR lLager AS LOG NO-UNDO.
- DEF BUFFER BKunBest FOR KunBest.
- DEF BUFFER BAufko FOR Aufko.
- /* ---------- 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
- &Scoped-define BROWSE-NAME Br_KunBest
- /* Internal Tables (found by Frame, Query & Browse Queries) */
- &Scoped-define INTERNAL-TABLES KunBest
- /* Definitions for BROWSE Br_KunBest */
- &Scoped-define FIELDS-IN-QUERY-Br_KunBest KunBest.Pos KunBest.Artnr ~
- KunBest.Inhalt KunBest.Jahr VBez @ VBez VInhalt @ VInhalt ~
- VAlk_Gehalt @ VAlk_Gehalt VKGebinde @ VKGebinde VVGebinde @ VVGebinde ~
- KunBest.Soll KunBest.Best
- &Scoped-define ENABLED-FIELDS-IN-QUERY-Br_KunBest
- &Scoped-define QUERY-STRING-Br_KunBest FOR EACH KunBest ~
- WHERE KunBest.Firma = GVFirma ~
- AND KunBest.Knr = XVKnr NO-LOCK
- &Scoped-define OPEN-QUERY-Br_KunBest OPEN QUERY Br_KunBest FOR EACH KunBest ~
- WHERE KunBest.Firma = GVFirma ~
- AND KunBest.Knr = XVKnr NO-LOCK.
- &Scoped-define TABLES-IN-QUERY-Br_KunBest KunBest
- &Scoped-define FIRST-TABLE-IN-QUERY-Br_KunBest KunBest
- /* Definitions for DIALOG-BOX D-Dialog */
- &Scoped-define OPEN-BROWSERS-IN-QUERY-D-Dialog ~
- ~{&OPEN-QUERY-Br_KunBest}
- /* Standard List Definitions */
- &Scoped-Define ENABLED-OBJECTS Br_KunBest
- /* Custom List Definitions */
- /* List-1,List-2,List-3,List-4,List-5,List-6 */
- /* _UIB-PREPROCESSOR-BLOCK-END */
- &ANALYZE-RESUME
- /* *********************** Control Definitions ********************** */
- /* Define a dialog box */
- /* Definitions of the field level widgets */
- /* Query definitions */
- &ANALYZE-SUSPEND
- DEFINE QUERY Br_KunBest FOR
- KunBest SCROLLING.
- &ANALYZE-RESUME
- /* Browse definitions */
- DEFINE BROWSE Br_KunBest
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _DISPLAY-FIELDS Br_KunBest D-Dialog _STRUCTURED
- QUERY Br_KunBest DISPLAY
- KunBest.Pos FORMAT "zzz9":U
- KunBest.Artnr FORMAT "999999":U
- KunBest.Inhalt FORMAT "9999":U
- KunBest.Jahr FORMAT "zzzz":U
- VBez @ VBez COLUMN-LABEL "Artikel" FORMAT "x(28)":U
- VInhalt @ VInhalt COLUMN-LABEL "Inhalt" FORMAT "zzzz":U
- VAlk_Gehalt @ VAlk_Gehalt COLUMN-LABEL "Vol%" FORMAT "z9.99":U
- VKGebinde @ VKGebinde COLUMN-LABEL "KGebinde" FORMAT "x(10)":U
- VVGebinde @ VVGebinde COLUMN-LABEL "VGebinde" FORMAT "x(10)":U
- KunBest.Soll FORMAT "zz,zzz":U
- KunBest.Best FORMAT "zz,zzz":U
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- WITH NO-ROW-MARKERS SEPARATORS SIZE 109 BY 15
- BGCOLOR 15 .
- /* ************************ Frame Definitions *********************** */
- DEFINE FRAME D-Dialog
- Br_KunBest AT ROW 1.24 COL 2
- SPACE(0.99) SKIP(0.23)
- WITH VIEW-AS DIALOG-BOX KEEP-TAB-ORDER
- SIDE-LABELS NO-UNDERLINE THREE-D SCROLLABLE
- TITLE "Faxbestellung".
- /* *********************** 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 */
- /* BROWSE-TAB Br_KunBest 1 D-Dialog */
- ASSIGN
- FRAME D-Dialog:SCROLLABLE = FALSE
- FRAME D-Dialog:HIDDEN = TRUE.
- /* _RUN-TIME-ATTRIBUTES-END */
- &ANALYZE-RESUME
- /* Setting information for Queries and Browse Widgets fields */
- &ANALYZE-SUSPEND _QUERY-BLOCK BROWSE Br_KunBest
- /* Query rebuild information for BROWSE Br_KunBest
- _TblList = "AnaDat.KunBest"
- _Where[1] = "KunBest.Firma = GVFirma
- AND KunBest.Knr = XVKnr"
- _FldNameList[1] = AnaDat.KunBest.Pos
- _FldNameList[2] = AnaDat.KunBest.Artnr
- _FldNameList[3] = AnaDat.KunBest.Inhalt
- _FldNameList[4] > AnaDat.KunBest.Jahr
- "KunBest.Jahr" ? "zzzz" "integer" ? ? ? ? ? ? no ? no no ? yes no no "U" "" "" "" "" "" "" 0 no 0 no no
- _FldNameList[5] > "_<CALC>"
- "VBez @ VBez" "Artikel" "x(28)" ? ? ? ? ? ? ? no ? no no ? yes no no "U" "" "" "" "" "" "" 0 no 0 no no
- _FldNameList[6] > "_<CALC>"
- "VInhalt @ VInhalt" "Inhalt" "zzzz" ? ? ? ? ? ? ? no ? no no ? yes no no "U" "" "" "" "" "" "" 0 no 0 no no
- _FldNameList[7] > "_<CALC>"
- "VAlk_Gehalt @ VAlk_Gehalt" "Vol%" "z9.99" ? ? ? ? ? ? ? no ? no no ? yes no no "U" "" "" "" "" "" "" 0 no 0 no no
- _FldNameList[8] > "_<CALC>"
- "VKGebinde @ VKGebinde" "KGebinde" "x(10)" ? ? ? ? ? ? ? no ? no no ? yes no no "U" "" "" "" "" "" "" 0 no 0 no no
- _FldNameList[9] > "_<CALC>"
- "VVGebinde @ VVGebinde" "VGebinde" "x(10)" ? ? ? ? ? ? ? no ? no no ? yes no no "U" "" "" "" "" "" "" 0 no 0 no no
- _FldNameList[10] > AnaDat.KunBest.Soll
- "KunBest.Soll" ? "zz,zzz" "integer" ? ? ? ? ? ? no ? no no ? yes no no "U" "" "" "" "" "" "" 0 no 0 no no
- _FldNameList[11] > AnaDat.KunBest.Best
- "KunBest.Best" ? "zz,zzz" "integer" ? ? ? ? ? ? no ? no no ? yes no no "U" "" "" "" "" "" "" 0 no 0 no no
- _Query is OPENED
- */ /* BROWSE Br_KunBest */
- &ANALYZE-RESUME
- &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 /* Faxbestellung */
- 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 BROWSE-NAME Br_KunBest
- &Scoped-define SELF-NAME Br_KunBest
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL Br_KunBest D-Dialog
- ON DELETE-CHARACTER OF Br_KunBest IN FRAME D-Dialog
- DO:
- DO WITH FRAME {&FRAME-NAME}:
- IF {&BROWSE-NAME}:NUM-SELECTED-ROWS = 0 THEN RETURN NO-APPLY.
- IF NOT AVAILABLE KunBest THEN RETURN NO-APPLY.
- Ja = TRUE.
- { v8/loeschen.i }
- IF NOT Ja THEN RETURN NO-APPLY.
- REPEAT TRANSACTION:
- FIND BKunBest WHERE RECID(BKunBest) = RECID(KunBest).
- DELETE BKunBest.
- {&BROWSE-NAME}:DELETE-SELECTED-ROW(1).
- LEAVE.
- END.
- END.
- END.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL Br_KunBest D-Dialog
- ON RETURN OF Br_KunBest IN FRAME D-Dialog
- DO:
- IF NOT AVAILABLE KunBest THEN RETURN NO-APPLY.
-
- DEF VAR VRecid AS RECID NO-UNDO.
- DEF BUFFER BKunbest FOR KunBest.
-
- FIND Artst NO-LOCK USE-INDEX Artst-k1
- WHERE Artst.Firma = KunBest.Firma
- AND Artst.Artnr = KunBest.Artnr
- AND Artst.Inhalt = KunBest.Inhalt
- AND Artst.Jahr = KunBest.Jahr.
-
- ASSIGN AVArtnr = Artst.Artnr
- AVInhalt = Artst.Inhalt
- AVJahr = Artst.Jahr
- LVKGeb_Cd = Artst.KGeb_Cd
- LVVGeb_Cd = Artst.VGeb_Cd
- LVGGeb_Cd = Artst.GGeb_Cd
- XVKGeb_Me = KunBest.KGeb_Me
- XVVGeb_Me = KunBest.VGeb_Me
- XVGGeb_Me = KunBest.GGeb_Me
- XVKGeb_Be = KunBest.KGeb_Me
- XVVGeb_Be = KunBest.VGeb_Me
- XVGGeb_Be = KunBest.GGeb_Me.
-
- VRecid = RECID(KunBest).
- VDaten = Artst.KGeb_Cd + ';'
- + Artst.VGeb_Cd + ';'
- + Artst.GGeb_Cd + ';'
- + STRING(KunBest.KGeb_Me) + ';'
- + STRING(KunBest.VGeb_Me) + ';'
- + STRING(KunBest.GGeb_Me) + ';'
- + STRING(RECID(Artst)) + ';'
- + STRING(Artst.Lager ,'yes/no') + ';'
- + STRING(iLager) + ';'
- + STRING(BAufko.AlsOfferte,'yes/no') + ';'
- + STRING(KunBest.KGeb_Me) + ';'
- + STRING(KunBest.VGeb_Me) + ';'
- + STRING(KunBest.GGeb_Me).
- RUN "g-gebindemenge.w" ( INPUT-OUTPUT VDaten ).
- IF VDaten = '' THEN RETURN NO-APPLY.
-
- XVGGeb_Me = DEC(ENTRY(1, VDaten, ';')).
- XVVGeb_Me = DEC(ENTRY(2, VDaten, ';')).
- XVKGeb_Me = DEC(ENTRY(3, VDaten, ';')).
- lLager = (IF ENTRY(4, VDaten, ';') BEGINS 'N' THEN FALSE ELSE TRUE).
- XVGGeb_Be = DEC(ENTRY(5, VDaten, ';')).
- XVVGeb_Be = DEC(ENTRY(6, VDaten, ';')).
- XVKGeb_Be = DEC(ENTRY(7, VDaten, ';')).
-
- REPEAT TRANSACTION:
- FIND BKunBest WHERE RECID(BKunBest) = VRecid.
- ASSIGN BKunBest.KGeb_Cd = Artst.KGeb_Cd
- BKunBest.VGeb_Cd = Artst.VGeb_Cd
- BKunBest.KGeb_Cd = Artst.GGeb_Cd
- BKunBest.KGeb_Me = XVKGeb_Me
- BKunBest.VGeb_Me = XVVGeb_Me
- BKunBest.GGeb_Me = XVGGeb_Me
- BKunBest.Best = XVKGeb_Me
- KunBest.Lag_Buch = lLager.
- RELEASE BKunBest.
- LEAVE.
- END.
- Br_KunBest:REFRESH().
- RETURN.
-
- END.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL Br_KunBest D-Dialog
- ON ROW-DISPLAY OF Br_KunBest IN FRAME D-Dialog
- DO:
- IF NOT AVAILABLE KunBest THEN RETURN NO-APPLY.
- FIND Artst USE-INDEX Artst-k1
- WHERE Artst.Firma = GVFirma
- AND Artst.Artnr = KunBest.Artnr
- AND Artst.Inhalt = KunBest.Inhalt
- AND Artst.Jahr = KunBest.Jahr NO-LOCK NO-ERROR.
- IF AVAILABLE Artst THEN DO:
- FIND KGebinde USE-INDEX KGebinde-k1
- WHERE KGebinde.Firma = KunBest.Firma
- AND KGebinde.Geb_Cd = Artst.KGeb_Cd NO-LOCK NO-ERROR.
- FIND VGebinde USE-INDEX VGebinde-k1
- WHERE VGebinde.Firma = KunBest.Firma
- AND VGebinde.Geb_Cd = Artst.VGeb_Cd NO-LOCK NO-ERROR.
- VBez = Artst.Bez.
- VInhalt = KGebinde.Inhalt.
- VAlk_Gehalt = Artst.Alk_Gehalt.
- VKGebinde = KGebinde.KBez.
- VVGebinde = VGebinde.KBez.
- END.
- END.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &UNDEFINE SELF-NAME
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK D-Dialog
- /* *************************** Main Block *************************** */
- FIND BAufko NO-LOCK USE-INDEX Aufko-k1
- WHERE BAufko.Firma = GVFirma
- AND BAufko.Aufnr = XVAufnr.
- ASSIGN iLager = BAufko.Lager.
- REPEAT TRANSACTION:
- FOR EACH KunBest USE-INDEX KunBest-k1
- WHERE KunBest.Firma = GVFirma
- AND KunBest.Knr = XVKnr :
- FIND Artst OF KunBest NO-LOCK NO-ERROR.
- IF NOT AVAILABLE Artst THEN DO:
- DELETE KunBest.
- NEXT.
- END.
- IF Artst.Aktiv = FALSE OR
- Artst.Ausverk = 9 THEN DO:
- DELETE KunBest.
- NEXT.
- END.
- END.
- LEAVE.
- END.
- {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 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.
- ------------------------------------------------------------------------------*/
- ENABLE Br_KunBest
- 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 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
- ------------------------------------------------------------------------------*/
- /* Define variables needed by this internal procedure. */
- {src/adm/template/snd-head.i}
- /* For each requested table, put it's ROWID in the output list. */
- {src/adm/template/snd-list.i "KunBest"}
- /* Deal with any unexpected table requests before closing. */
- {src/adm/template/snd-end.i}
- 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
|