| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518 |
- &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 VTitel AS CHAR.
- DEF VAR VArt AS INT.
- DEF VAR VFormat AS CHAR.
- DEF VAR VLabel AS CHAR.
- /* ---------- 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 first Frame and/or Browse and/or first Query */
- &Scoped-define FRAME-NAME D-Dialog
- /* Standard List Definitions */
- &Scoped-Define ENABLED-OBJECTS Btn_OK Btn_Cancel
- /* Custom List Definitions */
- /* List-1,List-2,List-3,List-4,List-5,List-6 */
- &Scoped-define List-1 F_Zeichen F_Datum F_Nummer F_Decimal
- /* _UIB-PREPROCESSOR-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
- BGCOLOR 8 .
- DEFINE BUTTON Btn_OK AUTO-GO
- LABEL "&OK"
- SIZE 15 BY 1
- BGCOLOR 8 .
- DEFINE VARIABLE F_Datum AS DATE FORMAT "99.99.9999":U
- LABEL "Fill 3"
- VIEW-AS FILL-IN NATIVE
- SIZE 14 BY .81
- BGCOLOR 15 NO-UNDO.
- DEFINE VARIABLE F_Decimal AS DECIMAL FORMAT "zzz,zz9.9999-":U INITIAL 0
- LABEL "Fill 4"
- VIEW-AS FILL-IN NATIVE
- SIZE 14 BY .81
- BGCOLOR 15 NO-UNDO.
- DEFINE VARIABLE F_Nummer AS INTEGER FORMAT "9999999":U INITIAL 0
- LABEL "Fill 1"
- VIEW-AS FILL-IN NATIVE
- SIZE 8.6 BY .81
- BGCOLOR 15 NO-UNDO.
- DEFINE VARIABLE F_Zeichen AS CHARACTER FORMAT "X(256)":U
- LABEL "Fill 2"
- VIEW-AS FILL-IN NATIVE
- SIZE 14 BY .81
- BGCOLOR 15 NO-UNDO.
- /* ************************ Frame Definitions *********************** */
- DEFINE FRAME D-Dialog
- F_Zeichen AT ROW 1.24 COL 34.2 COLON-ALIGNED
- F_Datum AT ROW 1.62 COL 44.8 COLON-ALIGNED
- F_Nummer AT ROW 1.91 COL 28.6 RIGHT-ALIGNED
- F_Decimal AT ROW 2.52 COL 31.2 COLON-ALIGNED
- Btn_OK AT ROW 3.19 COL 10.4
- Btn_Cancel AT ROW 3.19 COL 35
- SPACE(15.13) SKIP(0.49)
- WITH VIEW-AS DIALOG-BOX KEEP-TAB-ORDER
- SIDE-LABELS NO-UNDERLINE THREE-D SCROLLABLE
- TITLE "Einlesen Wert"
- DEFAULT-BUTTON Btn_OK CANCEL-BUTTON Btn_Cancel.
- /* *********************** 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
- */
- ASSIGN
- FRAME D-Dialog:SCROLLABLE = FALSE
- FRAME D-Dialog:HIDDEN = TRUE.
- /* SETTINGS FOR FILL-IN F_Datum IN FRAME D-Dialog
- NO-DISPLAY NO-ENABLE 1 */
- ASSIGN
- F_Datum:HIDDEN IN FRAME D-Dialog = TRUE.
- /* SETTINGS FOR FILL-IN F_Decimal IN FRAME D-Dialog
- NO-DISPLAY NO-ENABLE 1 */
- ASSIGN
- F_Decimal:HIDDEN IN FRAME D-Dialog = TRUE.
- /* SETTINGS FOR FILL-IN F_Nummer IN FRAME D-Dialog
- NO-DISPLAY NO-ENABLE ALIGN-R 1 */
- ASSIGN
- F_Nummer:HIDDEN IN FRAME D-Dialog = TRUE
- F_Nummer:MOVABLE IN FRAME D-Dialog = TRUE.
- /* SETTINGS FOR FILL-IN F_Zeichen IN FRAME D-Dialog
- NO-DISPLAY NO-ENABLE 1 */
- ASSIGN
- F_Zeichen:HIDDEN IN FRAME D-Dialog = TRUE.
- /* _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 /* Einlesen Wert */
- 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_OK
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CONTROL Btn_OK D-Dialog
- ON CHOOSE OF Btn_OK IN FRAME D-Dialog /* OK */
- DO:
- DO WITH FRAME {&FRAME-NAME}:
-
- ERROR-STATUS:ERROR = FALSE.
- CASE VArt:
-
- WHEN 1 THEN DO:
- F_Nummer = INTEGER(F_Nummer:SCREEN-VALUE) NO-ERROR.
- IF ERROR-STATUS:ERROR THEN Linktext = ?.
- ELSE Linktext = STRING(F_Nummer,VFormat).
- END.
-
- WHEN 2 THEN DO:
- F_Decimal = DECIMAL(F_Decimal:SCREEN-VALUE) NO-ERROR.
- IF ERROR-STATUS:ERROR THEN Linktext = ?.
- ELSE Linktext = STRING(F_Decimal,VFormat).
- END.
- WHEN 3 THEN DO:
- F_Datum = DATE(F_Datum:SCREEN-VALUE) NO-ERROR.
- IF ERROR-STATUS:ERROR OR
- F_Datum = ? THEN Linktext = ?.
- ELSE Linktext = STRING(F_Datum,VFormat).
- END.
- WHEN 4 THEN DO:
- F_Zeichen = F_Zeichen:SCREEN-VALUE NO-ERROR.
- IF ERROR-STATUS:ERROR THEN Linktext = ?.
- ELSE Linktext = STRING(F_Zeichen,VFormat).
- END.
- END.
- END.
- END.
- /* _UIB-CODE-BLOCK-END */
- &ANALYZE-RESUME
- &UNDEFINE SELF-NAME
- &ANALYZE-SUSPEND _UIB-CODE-BLOCK _CUSTOM _MAIN-BLOCK D-Dialog
- /* *************************** Main Block *************************** */
- /* Linktext: Vorgabe;Titel der Box;Label des Feldes;Format des Feldes;Art */
- /* Art = 1: INTEGER */
- /* 2: DECIMAL */
- /* 3: DATUM */
- /* 4: CHARACTER */
- DEF VAR VInhalt AS CHAR NO-UNDO.
- DEF VAR VAnzahl AS INT NO-UNDO.
- DEF VAR VPixels AS INT NO-UNDO.
- DEF VAR XH AS HANDLE NO-UNDO.
- DEF VAR VKA AS INT NO-UNDO.
- DEF VAR VKZ AS INT NO-UNDO.
- DEF VAR VLaenge AS INT NO-UNDO.
- VAnzahl = NUM-ENTRIES(Linktext, ";").
- VTitel = ''.
- VLabel = ''.
- VFormat = ''.
- VArt = 0.
- VInhalt = ENTRY(2, Linktext, ';').
- VTitel = VInhalt.
- VInhalt = ENTRY(3, Linktext, ';').
- VLabel = VInhalt.
- VInhalt = ENTRY(4, Linktext, ';').
- VFormat = VInhalt.
- VInhalt = ENTRY(5, Linktext, ';').
- VArt = INTEGER(VInhalt).
- VLaenge = LENGTH(VFormat).
- VKA = INDEX (VFormat, '(').
- VKZ = INDEX (VFormat, ')').
- IF VKA > 0 THEN DO:
- VKA = VKA + 1.
- VInhalt = SUBSTRING(VFormat,VKA,VKZ - VKA).
- VLaenge = VLaenge + INTEGER(VInhalt) - 2 - VKZ + VKA.
- END.
- VPixels = LENGTH(VFormat) * 9.5.
- FRAME {&FRAME-NAME}:TITLE = VTitel.
- DO WITH FRAME {&FRAME-NAME}:
- CASE VArt:
- WHEN 1 THEN DO:
- F_Nummer:X = 190.
- F_Nummer:Y = 25.
- F_Nummer:WIDTH-PIXELS = VPixels.
- F_Nummer:FORMAT = VFormat.
- F_Nummer:LABEL = VLabel.
- F_Nummer:HIDDEN = FALSE.
- F_Nummer:SENSITIVE = TRUE.
- XH = F_Nummer:SIDE-LABEL-HANDLE IN FRAME {&FRAME-NAME}.
- XH:X = 190 - (LENGTH(VLabel) * 9.5).
- XH:Y = 20.
-
- VInhalt = ENTRY(1, Linktext, ';').
- F_Nummer = INTEGER(VInhalt).
- DISPLAY F_Nummer.
- END.
-
- WHEN 2 THEN DO:
- F_Decimal:X = 190.
- F_Decimal:Y = 25.
- F_Decimal:WIDTH-PIXELS = VPixels.
- F_Decimal:FORMAT = VFormat.
- F_Decimal:LABEL = VLabel.
- F_Decimal:HIDDEN = FALSE.
- F_Decimal:SENSITIVE = TRUE.
- XH = F_Decimal:SIDE-LABEL-HANDLE IN FRAME {&FRAME-NAME}.
- XH:X = 190 - (LENGTH(VLabel) * 9.5).
- XH:Y = 20.
-
- VInhalt = ENTRY(1, Linktext, ';').
- F_Decimal = DECIMAL(VInhalt).
- DISPLAY F_Decimal.
- END.
-
- WHEN 3 THEN DO:
- F_Datum:X = 190.
- F_Datum:Y = 25.
- F_Datum:WIDTH-PIXELS = VPixels.
- F_Datum:FORMAT = VFormat.
- F_Datum:LABEL = VLabel.
- F_Datum:HIDDEN = FALSE.
- F_Datum:SENSITIVE = TRUE.
- XH = F_Datum:SIDE-LABEL-HANDLE IN FRAME {&FRAME-NAME}.
- XH:X = 190 - (LENGTH(VLabel) * 7).
- XH:Y = 20.
-
- VInhalt = ENTRY(1, Linktext, ';').
- IF VInhalt = '?' THEN F_Datum = ?.
- ELSE F_Datum = DATE(INTEGER(SUBSTRING(VInhalt,04,02)),
- INTEGER(SUBSTRING(VInhalt,01,02)),
- INTEGER(SUBSTRING(VInhalt,07,04))).
- DISPLAY F_Datum.
- END.
-
- WHEN 4 THEN DO:
- F_Zeichen:X = 190.
- F_Zeichen:Y = 25.
- F_Zeichen:WIDTH-PIXELS = VPixels.
- F_Zeichen:FORMAT = VFormat.
- F_Zeichen:LABEL = VLabel.
- F_Zeichen:HIDDEN = FALSE.
- F_Zeichen:SENSITIVE = TRUE.
- XH = F_Zeichen:SIDE-LABEL-HANDLE IN FRAME {&FRAME-NAME}.
- XH:X = 190 - (LENGTH(VLabel) * 9.5).
- XH:Y = 20.
-
- VInhalt = ENTRY(1, Linktext, ';').
- F_Zeichen = VInhalt.
- DISPLAY F_Zeichen.
- END.
-
- END CASE.
-
- Linktext = ''.
- 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 Btn_OK Btn_Cancel
- 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 local-initialize D-Dialog
- PROCEDURE local-initialize :
- /*------------------------------------------------------------------------------
- Purpose: Override standard ADM method
- Notes:
- ------------------------------------------------------------------------------*/
- RUN dispatch IN THIS-PROCEDURE ( INPUT 'initialize':U ) .
- 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
|