Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations SkipVought on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

EVENTS FOR ACUCORP

Status
Not open for further replies.

D2BEA

Technical User
Mar 13, 2001
41
0
0
US
I HAVE BUILT SCREENS, BUT I DO NOT KNOW HOW TO BUILD AN EVENT TO HAVE THE PUSH BUTTON PULL UP THE NEXT SCREEN.
 
Are you using the acubench? I have written a number of programs now using their gui tools and they work great. Also, what is the development system version?

Ted
 
Since you are waiting for a user to respond to the button you must keep the screen active until that happens. The simplest way is to use a PERFORM UNTIL structure:

PERFORM UNTIL BUTTON-CLICKED
DISPLAY SCREEN-A
ACCEPT SCREEN-A
END PERFORM.

"BUTTON-CLICKED" IS A CONDITION NAME IN WORKING STORAGE:

77 KEY-STATUS IS SPECIAL-NAMES CRT STATUS PIC 9(5) VALUE 0.
88 BUTTON-CLICKED VALUE 97.

THE VALUE OF BUTTON-CLICKED IS ARBITRARY AND IS WHATEVER YOU ASSIGNED TO THE TERMINATION-VALUE PROPERTY OF THE BUTTON. THE USER CLICKING ON THE BUTTON WILL CAUSE KEY-STATUS TO BECOME THE TERMINATION VALUE ASSIGNED AND WILL CAUSE THE PERFORM TO TERMINATE.

YOU CAN OF COURSE PUT SEVERAL BUTTONS ON YOUR SCREEN AND EXECUTE PROCEDURES AFTERWARD DEPENDING ON WHICH BUTTON WAS CLICKED.
 
I am using Acubench 5.1 and I am trying to use the AFTER procedure. The User enters a code and I have an AFTER procedure calling another program, it comes back to the user screen, but if I touch tab or enter or anything it runs thru the after procedure again.
 
Take a look at the tab order of each field. The after procedure for the field where the user enters the code won't be executed until after you press tab or enter. When you return from the called program, called by the after procedure, focus should be on the next field as specified by the tab order.

Ted
 
I set the tab order correctly, what happens is this. On one field it brings me back to the user screen and to the filed i was on and if it finds the code it keeps running through the procedure again, I do have the tab set to go to the next field. Another item I found is that if the code is incorrect it should not leave the field i until it is corrected but if you press return or tab a couple of times it will eventually go to the next field.
 
You control which field gets focus by setting the accept-control and the control-id fields. The control-id would contain the ID number for the field you want to return to. This should be set in your after procedure for the field.

Ted

 
You just confused me. If this is done in Acubench and the after procedure is built in-I'm not sure what you mean by your statement of setting the accept control?
 
You just confused me. If this is done in Acubench and the after procedure is built in-I'm not sure what you mean by your statement of setting the accept control?
 
Sorry for the confusion. Could you post your after procedure for the field you are having the problem with? That would make it easier to see what is going on.

Ted
 
FOR STATE FIELD

CS-HHINFO-CS1-STATE-EF-ADD-Aft-Procedure.
perform state-check.

STATE-CHECK.
IF HMFN-STATE = 'AK' OR 'AL' OR 'AZ' OR 'AR' OR 'CA' OR
'CO' OR 'CT' OR 'DE' OR 'DC' OR 'FL' OR
'GA' OR 'HI' OR 'ID' OR 'IL' OR 'IN' OR
'IA' OR 'KS' OR 'KY' OR 'LA' OR 'ME' OR
'MD' OR 'MA' OR 'MI' OR 'MN' OR 'MS' OR
'MO' OR 'MT' OR 'NE' OR 'NV' OR 'NH' OR
'NJ' OR 'NM' OR 'NY' OR 'NC' OR 'ND' OR
'OH' OR 'OK' OR 'OR' OR 'PA' OR 'RI' OR
'SC' OR 'SD' OR 'TN' OR 'TX' OR 'UT' OR
'VT' OR 'VA' OR 'WA' OR 'WV' OR 'WI' OR
'WY'
next sentence
ELSE
DISPLAY MESSAGE 'INVALID STATE CODE ENTRY'
END-IF.
STATE-CHECK-EXIT.
EXIT.


for county field-THIS ONE CALLS A PROGRAM AS WELL.

.

CS-HHINFO-CS1-county-EF-ADD-Aft-Procedure.
perform COUNTY-CHECK.

COUNTY-CHECK.
IF HMFN-COUNTY > SPACE
move spaces to cl-file, cnty-found
MOVE 'COUNTY.TBL ' TO CL-FILE
CALL "CNTY-LOC2" USING HMFN-COUNTY, CNTY-FOUND,
HMFN-LOCATION, LOC-FOUND,
CNTY-LOC-name, CNTY-LOC-table
CANCEL "CNTY-LOC2"
IF CNTY-FOUND NOT = 'Y'
DISPLAY MESSAGE 'INVALID COUNTY CODE'
END-IF
END-IF.

COUNTY-CHECK-EXIT.
EXIT.
called program

** ENVIRONMENT DIVISION.
CONFIGURATION SECTION.

SPECIAL-NAMES.
*{Bench}activex-def
*{Bench}end
FILE-CONTROL.
COPY "cnty-loc-file.sl".
*{Bench}end
DATA DIVISION.
FILE SECTION.
*{Bench}file
COPY "cnty-loc-file.fd".
*{Bench}end
WORKING-STORAGE SECTION.
*{Bench}acu-def
COPY "Acugui.Def".
COPY "Acucobol.Def".
COPY "Crtvars.Def".
COPY "Showmsg.Def".
*{Bench}end
*
*
01 CNT PIC 9(02) VALUE ZERO.
01 HH-IDX PIC 9(02).
01 CL-KEY PIC 9(02)
VALUE IS 1.
01 cnty-loc-stat PIC X(02).
01 END-OF-FILE PIC X(01).
88 ENDOFFILE VALUE "E".

*{Bench}copy-working
*{Bench}end
LINKAGE SECTION.
01 CNTY-LOC-NAME.
05 FILLER PIC X(10)
VALUE IS '\AISTABLE\'.
05 CL-FILE PIC X(12)
VALUE IS spaces.
01 HMFN-COUNTY PIC X(02).
01 CNTY-FOUND PIC X(01).

01 LOC-FOUND PIC X(01).

01 HMFN-LOCATION PIC X(02).
01 CNTY-LOC-TABLE.
03 CL-VALUES OCCURS 33 TIMES.
05 CLV PIC X(02).




*{Bench}end
SCREEN SECTION.
*{Bench}copy-screen
*{Bench}end
PROCEDURE DIVISION using HMFN-COUNTY, CNTY-FOUND,
HMFN-LOCATION, LOC-FOUND,
CNTY-LOC-name, CNTY-LOC-table.


A000-BEGIN.
MOVE SPACES TO cnty-loc-table.
OPEN INPUT CNTY-LOC-FILE.
PERFORM B000-READ.
CLOSE CNTY-LOC-FILE.
EXIT PROGRAM.
A000-EXIT.
EXIT.



B000-READ.
MOVE 'N' TO END-OF-FILE.
PERFORM UNTIL ENDOFFILE
READ CNTY-LOC-FILE INTO CNTY-LOC-TABLE
INVALID KEY
MOVE "E" TO END-OF-FILE
NOT INVALID KEY
PERFORM C000-CHECK
END-READ
END-PERFORM.
B000-EXIT.
EXIT.

C000-CHECK.
COMPUTE CNT = CNT + 1.
IF CL-FILE = 'COUNTY.TBL'
PERFORM C100-COUNTY
ELSE
PERFORM C200-LOCATION
END-IF.


C100-COUNTY.
MOVE 'N' TO CNTY-FOUND.
perform varying hh-idx from 1 by 1
UNTIL HH-IDX > 33
OR
CLV(HH-IDX) = SPACES
IF HMFN-COUNTY = CLV(HH-IDX)
MOVE 'Y' TO CNTY-FOUND
move 'E' to end-of-file
END-IF
END-PERFORM.


C200-LOCATION.
MOVE 'N' TO LOC-FOUND.
perform varying hh-idx from 1 by 1
UNTIL HH-IDX > 33
OR
CLV(HH-IDX) = SPACES
IF HMFN-LOCATION = CLV(HH-IDX)
MOVE 'Y' TO LOC-FOUND
move 'E' to end-of-file
END-IF
END-PERFORM.

C200-EXIT.
EXIT.

 
Sorry, I didn't realize how hard it would be to debug an acubench program without seeing all of the elements. Have you tried running debug on it?

Ted
 
You need to simplify! The state list is a perfect candidate for a drop down list box. With a list box there is no need for an after procedure to validate input the user can only selected a valid code! Just take the sample list box program and use the state names as the data. Every sample program is useable in a real world applications. I have developed whole systems just copying and pasting from those sample programs and making slight modifications.

Regards

Vins Nash
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top