| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548 |
- &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:
- <none>
- Output Parameters:
- <none>
- ------------------------------------------------------------------------*/
- /* 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 VText AS CHAR FORMAT "x(30)" NO-UNDO.
- DEF VAR Vorhanden AS LOG NO-UNDO.
- /* ---------- 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_Artbw
- /* External Tables */
- &Scoped-define EXTERNAL-TABLES Artst
- &Scoped-define FIRST-EXTERNAL-TABLE Artst
- /* Need to scope the external tables to this procedure */
- DEFINE QUERY external_tables FOR Artst.
- /* Internal Tables (found by Frame, Query & Browse Queries) */
- &Scoped-define INTERNAL-TABLES Artbw
- /* Define KEY-PHRASE in case it is used by any query. */
- &Scoped-define KEY-PHRASE TRUE
- /* Definitions for BROWSE br_Artbw */
- &Scoped-define FIELDS-IN-QUERY-br_Artbw Artbw.Artnr Artbw.Inhalt Artbw.Jahr ~
- Artbw.Bez1 Artbw.Tr_Art VText @ VText Artbw.Datum Artbw.KGeb_Me ~
- Artbw.VGeb_Me Artbw.GGeb_Me Artbw.Lager
- &Scoped-define ENABLED-FIELDS-IN-QUERY-br_Artbw
- &Scoped-define OPEN-QUERY-br_Artbw OPEN QUERY br_Artbw FOR EACH Artbw WHERE Artbw.Firma = Artst.Firma ~
- AND Artbw.Artnr = Artst.Artnr NO-LOCK ~
- ~{&SORTBY-PHRASE}.
- &Scoped-define TABLES-IN-QUERY-br_Artbw Artbw
- &Scoped-define FIRST-TABLE-IN-QUERY-br_Artbw Artbw
- /* Definitions for FRAME F-Main */
- /* Standard List Definitions */
- &Scoped-Define ENABLED-OBJECTS br_Artbw RECT-1
- /* 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
- <KEY-OBJECT>
- &BROWSE-NAME
- </KEY-OBJECT>
- <FOREIGN-KEYS>
- FRW||y|AnaDat.Artbw.FRW
- Firma||y|AnaDat.Artbw.Firma
- Trnr||y|AnaDat.Artbw.Trnr
- </FOREIGN-KEYS>
- <EXECUTING-CODE>
- **************************
- * Set attributes related to FOREIGN KEYS
- */
- RUN set-attribute-list (
- 'Keys-Accepted = ,
- Keys-Supplied = "FRW,Firma,Trnr"':U).
- /* Tell the ADM to use the OPEN-QUERY-CASES. */
- &Scoped-define OPEN-QUERY-CASES RUN dispatch ('open-query-cases':U).
- /**************************
- </EXECUTING-CODE> */
- /* _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
- <KEY-OBJECT>
- &BROWSE-NAME
- </KEY-OBJECT>
- <SORTBY-OPTIONS>
- </SORTBY-OPTIONS>
- <SORTBY-RUN-CODE>
- ************************
- * Set attributes related to SORTBY-OPTIONS */
- RUN set-attribute-list (
- 'SortBy-Options = ""':U).
- /************************
- </SORTBY-RUN-CODE>
- <FILTER-ATTRIBUTES>
- </FILTER-ATTRIBUTES> */
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- /* *********************** Control Definitions ********************** */
- /* Definitions of the field level widgets */
- DEFINE RECTANGLE RECT-1
- EDGE-PIXELS 2 GRAPHIC-EDGE NO-FILL
- SIZE 114 BY 10.48.
- /* Query definitions */
- &ANALYZE-SUSPEND
- DEFINE QUERY br_Artbw FOR
- Artbw SCROLLING.
- &ANALYZE-RESUME
- /* Browse definitions */
- DEFINE BROWSE br_Artbw
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _DISPLAY-FIELDS br_Artbw B-table-Win _STRUCTURED
- QUERY br_Artbw NO-LOCK DISPLAY
- Artbw.Artnr FORMAT "999999":U
- Artbw.Inhalt FORMAT "9999":U
- Artbw.Jahr FORMAT "9999":U
- Artbw.Bez1 COLUMN-LABEL "Artikel" FORMAT "x(25)":U
- Artbw.Tr_Art COLUMN-LABEL "BA" FORMAT "99":U
- VText @ VText COLUMN-LABEL "Transaktionsart" FORMAT "x(20)":U
- Artbw.Datum FORMAT "99.99.9999":U
- Artbw.KGeb_Me COLUMN-LABEL "KGeb" FORMAT "zzzz9-":U
- Artbw.VGeb_Me COLUMN-LABEL "VGeb" FORMAT "zzzz9-":U
- Artbw.GGeb_Me COLUMN-LABEL "GGeb" FORMAT "zzzz9-":U
- Artbw.Lager COLUMN-LABEL "LG" FORMAT "99":U
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- WITH NO-ASSIGN NO-ROW-MARKERS SEPARATORS SIZE 112 BY 10
- BGCOLOR 15 .
- /* ************************ Frame Definitions *********************** */
- DEFINE FRAME F-Main
- br_Artbw AT ROW 1.48 COL 3
- RECT-1 AT ROW 1.24 COL 2
- WITH 1 DOWN NO-BOX KEEP-TAB-ORDER OVERLAY
- SIDE-LABELS NO-UNDERLINE THREE-D
- AT COL 1 ROW 1 SCROLLABLE .
- /* *********************** Procedure Settings ************************ */
- &ANALYZE-SUSPEND _PROCEDURE-SETTINGS
- /* Settings for THIS-PROCEDURE
- Type: SmartBrowser
- External Tables: AnaDat.Artst
- 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 = 11
- WIDTH = 117.2.
- /* 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_Artbw 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_Artbw
- /* Query rebuild information for BROWSE br_Artbw
- _TblList = "AnaDat.Artbw WHERE AnaDat.Artst ..."
- _Options = "NO-LOCK KEY-PHRASE SORTBY-PHRASE"
- _JoinCode[1] = "Artbw.Firma = Artst.Firma
- AND Artbw.Artnr = Artst.Artnr"
- _FldNameList[1] = AnaDat.Artbw.Artnr
- _FldNameList[2] = AnaDat.Artbw.Inhalt
- _FldNameList[3] = AnaDat.Artbw.Jahr
- _FldNameList[4] > AnaDat.Artbw.Bez1
- "Artbw.Bez1" "Artikel" "x(25)" "character" ? ? ? ? ? ? no ? no no ? yes no no "U" "" ""
- _FldNameList[5] > AnaDat.Artbw.Tr_Art
- "Artbw.Tr_Art" "BA" ? "integer" ? ? ? ? ? ? no ? no no ? yes no no "U" "" ""
- _FldNameList[6] > "_<CALC>"
- "VText @ VText" "Transaktionsart" "x(20)" ? ? ? ? ? ? ? no ? no no ? yes no no "U" "" ""
- _FldNameList[7] = AnaDat.Artbw.Datum
- _FldNameList[8] > AnaDat.Artbw.KGeb_Me
- "Artbw.KGeb_Me" "KGeb" "zzzz9-" "decimal" ? ? ? ? ? ? no ? no no ? yes no no "U" "" ""
- _FldNameList[9] > AnaDat.Artbw.VGeb_Me
- "Artbw.VGeb_Me" "VGeb" "zzzz9-" "decimal" ? ? ? ? ? ? no ? no no ? yes no no "U" "" ""
- _FldNameList[10] > AnaDat.Artbw.GGeb_Me
- "Artbw.GGeb_Me" "GGeb" "zzzz9-" "decimal" ? ? ? ? ? ? no ? no no ? yes no no "U" "" ""
- _FldNameList[11] > AnaDat.Artbw.Lager
- "Artbw.Lager" "LG" ? "integer" ? ? ? ? ? ? no ? no no ? yes no no "U" "" ""
- _Query is NOT OPENED
- */ /* BROWSE br_Artbw */
- &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_Artbw
- &Scoped-define SELF-NAME br_Artbw
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_Artbw B-table-Win
- ON ROW-DISPLAY OF br_Artbw IN FRAME F-Main
- DO:
- RUN ANZEIGE.
- END.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_Artbw B-table-Win
- ON ROW-ENTRY OF br_Artbw IN FRAME F-Main
- DO:
- {src/adm/template/brsentry.i}
- END.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_Artbw B-table-Win
- ON ROW-LEAVE OF br_Artbw IN FRAME F-Main
- DO:
- {src/adm/template/brsleave.i}
- END.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL br_Artbw B-table-Win
- ON VALUE-CHANGED OF br_Artbw IN FRAME F-Main
- DO:
- {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 *************************** */
- &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-open-query-cases B-table-Win adm/support/_adm-opn.p
- PROCEDURE adm-open-query-cases :
- /*------------------------------------------------------------------------------
- Purpose: Opens different cases of the query based on attributes
- such as the 'Key-Name', or 'SortBy-Case'
- Parameters: <none>
- ------------------------------------------------------------------------------*/
- /* No Foreign keys are accepted by this SmartObject. */
- {&OPEN-QUERY-{&BROWSE-NAME}}
- END PROCEDURE.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &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: <none>
- ------------------------------------------------------------------------------*/
- /* Define variables needed by this internal procedure. */
- {src/adm/template/row-head.i}
- /* Create a list of all the tables that we need to get. */
- {src/adm/template/row-list.i "Artst"}
- /* Get the record ROWID's from the RECORD-SOURCE. */
- {src/adm/template/row-get.i}
- /* FIND each record specified by the RECORD-SOURCE. */
- {src/adm/template/row-find.i "Artst"}
- /* 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 ANZEIGE B-table-Win
- PROCEDURE ANZEIGE :
- /*------------------------------------------------------------------------------
- Purpose:
- Parameters: <none>
- Notes:
- ------------------------------------------------------------------------------*/
- VText = ''.
- IF NOT AVAILABLE Artbw THEN RETURN.
- FIND Tabel USE-INDEX Tabel-k1
- WHERE Tabel.Firma = GVFirma
- AND Tabel.RecArt = 'LAGKORR'
- AND Tabel.CodeC = ''
- AND Tabel.CodeI = Artbw.Tr_Art
- AND Tabel.Sprcd = 0 NO-LOCK NO-ERROR.
- IF AVAILABLE Tabel THEN VText = Tabel.Bez1.
- ELSE VText = FILL('?', 10).
- 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: <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 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:
- ------------------------------------------------------------------------------*/
- IF NUM-RESULTS('Br_Artbw':U) <> ? THEN CLOSE QUERY Br_Artbw.
-
- Vorhanden = FALSE.
- IF NOT AVAILABLE Artst THEN RETURN.
-
- OPEN QUERY Br_Artbw
- FOR EACH Artbw USE-INDEX Artbw-k7
- WHERE Artbw.Firma = Artst.Firma
- AND Artbw.Artnr = Artst.Artnr
- AND Artbw.Inhalt = Artst.Inhalt
- AND Artbw.Jahr = Artst.Jahr
- AND Artbw.Tr_Art > 10
- AND Artbw.Tr_Art < 21
- AND Artbw.Knr = 0 NO-LOCK.
- DO WHILE TRUE WITH FRAME {&FRAME-NAME}:
- IF NUM-RESULTS('Br_Artbw':U) = ? THEN LEAVE.
- IF NUM-RESULTS('Br_Artbw':U) = 0 THEN LEAVE.
- Vorhanden = TRUE.
- LEAVE.
- END.
-
- END PROCEDURE.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _PROCEDURE send-key B-table-Win adm/support/_key-snd.p
- PROCEDURE send-key :
- /*------------------------------------------------------------------------------
- Purpose: Sends a requested KEY value back to the calling
- SmartObject.
- Parameters: <see adm/template/sndkytop.i>
- ------------------------------------------------------------------------------*/
- /* Define variables needed by this internal procedure. */
- {src/adm/template/sndkytop.i}
- /* Return the key value associated with each key case. */
- {src/adm/template/sndkycas.i "FRW" "Artbw" "FRW"}
- {src/adm/template/sndkycas.i "Firma" "Artbw" "Firma"}
- {src/adm/template/sndkycas.i "Trnr" "Artbw" "Trnr"}
- /* Close the CASE statement and end the procedure. */
- {src/adm/template/sndkyend.i}
- 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 "Artst"}
- {src/adm/template/snd-list.i "Artbw"}
- /* 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: <none>
- 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
|