&ANALYZE-SUSPEND _VERSION-NUMBER UIB_v8r12 GUI ADM1 &ANALYZE-RESUME /* Connected Databases anadat PROGRESS */ &Scoped-define WINDOW-NAME CURRENT-WINDOW &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _DEFINITIONS B-table-Win /*------------------------------------------------------------------------ File: Description: from BROWSER.W - Basic SmartBrowser Object Template Input Parameters: Output Parameters: ------------------------------------------------------------------------*/ /* 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 VCodeI AS INT NO-UNDO. DEF BUFFER BTabel FOR Tabel. /* ---------- 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 SmartBrowser &Scoped-define DB-AWARE no &Scoped-define ADM-SUPPORTED-LINKS Record-Source,Record-Target,TableIO-Target /* Name of first Frame and/or Browse and/or first Query */ &Scoped-define FRAME-NAME F-Main &Scoped-define BROWSE-NAME br_table /* Internal Tables (found by Frame, Query & Browse Queries) */ &Scoped-define INTERNAL-TABLES Tabel /* Define KEY-PHRASE in case it is used by any query. */ &Scoped-define KEY-PHRASE TRUE /* Definitions for BROWSE br_table */ &Scoped-define FIELDS-IN-QUERY-br_table Tabel.Bez1 Tabel.Bez2 &Scoped-define ENABLED-FIELDS-IN-QUERY-br_table &Scoped-define OPEN-QUERY-br_table OPEN QUERY br_table FOR EACH Tabel WHERE ~{&KEY-PHRASE} ~ AND Tabel.Firma = LVFirma ~ AND Tabel.Recart = LVRecArt ~ AND Tabel.CodeC = "" ~ AND Tabel.Sprcd = LVSprcd NO-LOCK ~ ~{&SORTBY-PHRASE}. &Scoped-define TABLES-IN-QUERY-br_table Tabel &Scoped-define FIRST-TABLE-IN-QUERY-br_table Tabel /* Definitions for FRAME F-Main */ /* Standard List Definitions */ &Scoped-Define ENABLED-OBJECTS br_table /* Custom List Definitions */ /* List-1,List-2,List-3,List-4,List-5,List-6 */ /* _UIB-PREPROCESSOR-BLOCK-END */ &ANALYZE-RESUME &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Foreign Keys" B-table-Win _INLINE /* Actions: ? adm/support/keyedit.w ? ? ? */ /* STRUCTURED-DATA &BROWSE-NAME ************************** * Set attributes related to FOREIGN KEYS */ RUN set-attribute-list ( 'Keys-Accepted = "", Keys-Supplied = ""':U). /************************** */ /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME &ANALYZE-SUSPEND _UIB-CODE-BLOCK _XFTR "Advanced Query Options" B-table-Win _INLINE /* Actions: ? adm/support/advqedit.w ? ? ? */ /* STRUCTURED-DATA &BROWSE-NAME ************************ * Set attributes related to SORTBY-OPTIONS */ RUN set-attribute-list ( 'SortBy-Options = ""':U). /************************ */ /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME /* *********************** Control Definitions ********************** */ /* Definitions of the field level widgets */ /* Query definitions */ &ANALYZE-SUSPEND DEFINE QUERY br_table FOR Tabel SCROLLING. &ANALYZE-RESUME /* Browse definitions */ DEFINE BROWSE br_table &ANALYZE-SUSPEND _UIB-CODE-BLOCK _DISPLAY-FIELDS br_table B-table-Win _STRUCTURED QUERY br_table NO-LOCK DISPLAY Tabel.Bez1 COLUMN-LABEL "Bezeichnung 1" FORMAT "x(25)":U Tabel.Bez2 COLUMN-LABEL "Bezeichnung 2" FORMAT "x(25)":U /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME WITH NO-ASSIGN NO-ROW-MARKERS SEPARATORS SIZE 56 BY 6.19 BGCOLOR 15 . /* ************************ Frame Definitions *********************** */ DEFINE FRAME F-Main br_table AT ROW 1 COL 1 WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY SIDE-LABELS NO-UNDERLINE THREE-D AT COL 1 ROW 1 SCROLLABLE BGCOLOR 8 FGCOLOR 0 . /* *********************** Procedure Settings ************************ */ &ANALYZE-SUSPEND _PROCEDURE-SETTINGS /* Settings for THIS-PROCEDURE Type: SmartBrowser Allow: Basic,Browse Frames: 1 Add Fields to: EXTERNAL-TABLES Other Settings: PERSISTENT-ONLY COMPILE */ /* This procedure should always be RUN PERSISTENT. Report the error, */ /* then cleanup and return. */ IF NOT THIS-PROCEDURE:PERSISTENT THEN DO: MESSAGE "{&FILE-NAME} should only be RUN PERSISTENT.":U VIEW-AS ALERT-BOX ERROR BUTTONS OK. RETURN. END. &ANALYZE-RESUME _END-PROCEDURE-SETTINGS /* ************************* Create Window ************************** */ &ANALYZE-SUSPEND _CREATE-WINDOW /* DESIGN Window definition (used by the UIB) CREATE WINDOW B-table-Win ASSIGN HEIGHT = 6.57 WIDTH = 72.6. /* END WINDOW DEFINITION */ */ &ANALYZE-RESUME &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _INCLUDED-LIB B-table-Win /* ************************* Included-Libraries *********************** */ {src/adm/method/browser.i} /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME /* *********** Runtime Attributes and AppBuilder Settings *********** */ &ANALYZE-SUSPEND _RUN-TIME-ATTRIBUTES /* SETTINGS FOR WINDOW B-table-Win NOT-VISIBLE,,RUN-PERSISTENT */ /* SETTINGS FOR FRAME F-Main NOT-VISIBLE Size-to-Fit */ /* BROWSE-TAB br_table 1 F-Main */ ASSIGN FRAME F-Main:SCROLLABLE = FALSE FRAME F-Main:HIDDEN = TRUE. /* _RUN-TIME-ATTRIBUTES-END */ &ANALYZE-RESUME /* Setting information for Queries and Browse Widgets fields */ &ANALYZE-SUSPEND _QUERY-BLOCK BROWSE br_table /* Query rebuild information for BROWSE br_table _TblList = "AnaDat.Tabel" _Options = "NO-LOCK KEY-PHRASE SORTBY-PHRASE" _Where[1] = "Tabel.Firma = LVFirma AND Tabel.Recart = LVRecArt AND Tabel.CodeC = """" AND Tabel.Sprcd = LVSprcd" _FldNameList[1] > AnaDat.Tabel.Bez1 "Tabel.Bez1" "Bezeichnung 1" "x(25)" "character" ? ? ? ? ? ? no ? no no ? yes no no "U" "" "" _FldNameList[2] > AnaDat.Tabel.Bez2 "Tabel.Bez2" "Bezeichnung 2" "x(25)" "character" ? ? ? ? ? ? no ? no no ? yes no no "U" "" "" _Query is NOT OPENED */ /* BROWSE br_table */ &ANALYZE-RESUME &ANALYZE-SUSPEND _QUERY-BLOCK FRAME F-Main /* Query rebuild information for FRAME F-Main _Options = "NO-LOCK" _Query is NOT OPENED */ /* FRAME F-Main */ &ANALYZE-RESUME /* ************************ Control Triggers ************************ */ &Scoped-define BROWSE-NAME br_table &Scoped-define SELF-NAME br_table &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win ON ROW-ENTRY OF br_table IN FRAME F-Main DO: /* This code displays initial values for newly added or copied rows. */ {src/adm/template/brsentry.i} END. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win ON ROW-LEAVE OF br_table IN FRAME F-Main DO: /* Do not disable this code or no updates will take place except by pressing the Save button on an Update SmartPanel. */ {src/adm/template/brsleave.i} END. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_table B-table-Win ON VALUE-CHANGED OF br_table IN FRAME F-Main DO: IF AVAILABLE Tabel THEN DO: LVCodeI = Tabel.CodeI. END. {src/adm/template/brschnge.i} END. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME &UNDEFINE SELF-NAME &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK B-table-Win /* *************************** Main Block *************************** */ VCodeI = LVCodeI. &IF DEFINED(UIB_IS_RUNNING) <> 0 &THEN RUN dispatch IN THIS-PROCEDURE ('initialize':U). &ENDIF /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME /* ********************** Internal Procedures *********************** */ &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE adm-row-available B-table-Win _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: ------------------------------------------------------------------------------*/ /* 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 B-table-Win _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 F-Main. IF THIS-PROCEDURE:PERSISTENT THEN DELETE PROCEDURE THIS-PROCEDURE. END PROCEDURE. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE local-open-query B-table-Win PROCEDURE local-open-query : /*------------------------------------------------------------------------------ Purpose: Override standard ADM method Notes: ------------------------------------------------------------------------------*/ RUN dispatch IN THIS-PROCEDURE ('open-query':U). DO WITH FRAME {&FRAME-NAME}: IF NUM-RESULTS("{&BROWSE-NAME}":U) = ? THEN RETURN. IF NUM-RESULTS("{&BROWSE-NAME}":U) = 0 THEN RETURN. APPLY 'VALUE-CHANGED' TO BROWSE {&BROWSE-NAME}. END. FIND BTabel USE-INDEX Tabel-k1 WHERE BTabel.Firma = LVFirma AND BTabel.RecArt = LVRecArt AND BTabel.CodeC = '' AND BTabel.CodeI = VCodeI AND BTabel.Sprcd = LVSprcd NO-LOCK NO-ERROR. IF AVAILABLE BTabel THEN DO: REPOSITION {&BROWSE-NAME} TO ROWID ROWID(BTabel). APPLY 'VALUE-CHANGED' TO BROWSE {&BROWSE-NAME}. END. END PROCEDURE. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-records B-table-Win _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 "Tabel"} /* 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 B-table-Win PROCEDURE state-changed : /* ----------------------------------------------------------- Purpose: Parameters: Notes: -------------------------------------------------------------*/ DEFINE INPUT PARAMETER p-issuer-hdl AS HANDLE NO-UNDO. DEFINE INPUT PARAMETER p-state AS CHARACTER NO-UNDO. CASE p-state: /* Object instance CASEs can go here to replace standard behavior or add new cases. */ {src/adm/template/bstates.i} END CASE. END PROCEDURE. /* _UIB-CODE-BLOCK-END */ &ANALYZE-RESUME