I'm porting a Fortran program to z/OS designed for interactivity (like TSO). The program has an interrupt handling subroutine but a way is needed to direct a user interrupt (e.g. ATTN/PA1) to the Fortran interrupt-handler subroutine. That subroutine informs the program that a user wants to enter a command and so at the next opportunity, a command prompt is given to the user.
I ran across the assembler STAX macro which is an ATTN/PA1 interrupt handler. Has anyone here used the STAX assembler macro to control user interrupts in a running program?
The Fortran interrupt-handling subroutine is called BREAK. When invoking an assembler subroutine that runs the STAX macro, the address of the caller's parameter list is in R1. I'm thinking the address of the BREAK subroutine needs to be given in the macro parameter, ATTNEXIT. Subsequently, when the ATTN key is pressed, the interrupt handler would pass control to the BREAK subroutine and the program would respond as designed. However, there are a lot of other parameters in the STAX macro that don't seem relevant to my program. It is not clear to me that any or all of them can be ignored.
Any advice about this before I start running "smoke tests" would be most welcome.
Joined: 30 Nov 2013 Posts: 917 Location: The Universe
I'm not sure how useful this will be for you.
The ONLY "production" program I have where I use STAX has a STAX exit that "posts" an ECB that the program waits on. The mainline gets control and if the ECB the exit "posted" (there is at least one other ECB in the program) was set the program terminates.
A long, long time ago when I was thinking about something like what I think you want to do I concluded the only useful thing was for the STAX exit to ABEND. The ESTAE exit would intercept the ABEND in the STAX exit and the ESTAE "recovery" routine would do what I think you want to do. I decided there were too many program states involved in this for anything useful to come out of it and never tried to implement the idea.
the point is that it is <reasonably> easy to do it in an assembler environment
a bit more complicated when HLL are involved.
the problem is <similar> to the one I had a looong time ago ( when computers were a bit slower )
for a program that would run for more that 2 days ,
an rather that flooding the console whit messages ( NO SDSF AVAIL at thattime )
I implemented the infrastructure for the modify command
called a stub passing the address of a communication area
the stub would attach a subtask to wait for the modify command
and set the proper flags into the communication area
the main program loop would test the communication area
and based on the test, just display the processing counts or stop the program at a syncronisation point
probably the same approach might be used for stax
when an attention detected set the proper flags and reinstate the stax environment
the only overhead would be - at each loop - a test on the flag
Joined: 30 Nov 2013 Posts: 917 Location: The Universe
enrico-sorichetti wrote:
probably the same approach might be used for stax
when an attention detected set the proper flags and reinstate the stax environment
the only overhead would be - at each loop - a test on the flag
Once the STAX environment is defined it is not necessary to reinstate it after the STAX exit processes an attention interrupt.
The ONLY "production" program I have where I use STAX has a STAX exit that "posts" an ECB that the program waits on. The mainline gets control and if the ECB the exit "posted" (there is at least one other ECB in the program) was set the program terminates.
A long, long time ago when I was thinking about something like what I think you want to do I concluded the only useful thing was for the STAX exit to ABEND. The ESTAE exit would intercept the ABEND in the STAX exit and the ESTAE "recovery" routine would do what I think you want to do. I decided there were too many program states involved in this for anything useful to come out of it and never tried to implement the idea.
So, good luck.
For my purposes, the ATTN interrupt handler needs to set one or more flags inside the Fortran program's COMMON block, then resume the interrupted program.
Joined: 30 Nov 2013 Posts: 917 Location: The Universe
mxgdontmics wrote:
For my purposes, the ATTN interrupt handler needs to set one or more flags inside the Fortran program's COMMON block, then resume the interrupted program.
The storage can be almost anywhere; it does not have to be in Fortran "common" storage. The problem is the exit has to get addressability to the storage.
I don't really know how modern Fortran compilers implement "common" storage. In the 1960s "common" storage was defined in the load module as the equivalent of the Assembler COM statement. "Named" "common" storage might be defined by the equivalent of a NAME COM Assembler statement or a NAME CSECT statement if the storage was being initialized. Accessing data in "common" would, theoretically be quite easy More modern compilers may not use this scheme; "common" storage is obtained by GETMAIN. The program I took a quick look at to remind myself how the exit routines work uses this scheme, too; the STAX exit routine had some planning to get addressability to the ECBs it used as the equivalent of your flags.
One other issue you must be aware about is the STAX exit could potentially run while your program is running on another physical CPU so you must be aware of serialization issues using storage shared by your program and the STAX exit.
It turned out the execution state issues that puzzled me long, long ago was probably not as much a problem as I feared 30 or 40 years ago.
For my purposes, the ATTN interrupt handler needs to set one or more flags inside the Fortran program's COMMON block, then resume the interrupted program.
The storage can be almost anywhere; it does not have to be in Fortran "common" storage. The problem is the exit has to get addressability to the storage.
I don't really know how modern Fortran compilers implement "common" storage. In the 1960s "common" storage was defined in the load module as the equivalent of the Assembler COM statement. "Named" "common" storage might be defined by the equivalent of a NAME COM Assembler statement or a NAME CSECT statement if the storage was being initialized. Accessing data in "common" would, theoretically be quite easy More modern compilers may not use this scheme; "common" storage is obtained by GETMAIN. The program I took a quick look at to remind myself how the exit routines work uses this scheme, too; the STAX exit routine had some planning to get addressability to the ECBs it used as the equivalent of your flags.
One other issue you must be aware about is the STAX exit could potentially run while your program is running on another physical CPU so you must be aware of serialization issues using storage shared by your program and the STAX exit.
It turned out the execution state issues that puzzled me long, long ago was probably not as much a problem as I feared 30 or 40 years ago.
* THIS CODING EXAMPLE ISSUES A STAX MACRO INSTRUCTION TO SET UP AN
* ATTENTION EXIT.
*
* PROCESSING
* .
* .
* .
*
LA 3,STAXLIST
* ISSUE THE EXECUTE FORM OF THE STAX MACRO INSTRUCTION
*
STAX ATTNEXIT,OBUF=(OUTBUF,31),IBUF=(INBUF,140),MF=(E,(3))
*
* CHECK THE RETURN CODE FROM THE STAX SERVICE ROUTINE. A ZERO RETURN
* CODE INDICATES SUCCESSFUL COMPLETION.
*
LTR 15,15
BNZ ERRTN
*
* PROCESSING
*
ERRTN ERROR HANDLING ROUTINE
* .
* .
* .
ATTNEXIT ATTENTION EXIT ROUTINE
* .
* .
* .
*
*
* STORAGE DECLARATIONS
*
STAXLIST STAX ATTNEXIT,MF=L THIS LIST FORM OF THE STAX
* MACRO INSTRUCTION EXPANDS AND
* PROVIDES SPACE FOR THE STAX
* PARAMETER LIST
*
OUTBUF DC C'THIS IS A SAMPLE ATTENTION EXIT'
DS 0F
INBUF DC CL140'0' INITIALIZE 140 BYTES TO ZERO
* AS THE INPUT BUFFER
*
END
I haven't done a lot of assembler programming so I'm probably lacking a lot of "frame of reference" for the STAX documentation. Some fundamental questions remain, for me at least.
Since this is intended to be setup from a Fortran program (not VS Fortran so no LE environement), I'm thinking this macro will be run as an assembler subroutine called at the outset by the Fortran MAIN program. From that call, I should be able to obtain a parameter list through R1, i.e. the address to the logical flags in the Fortran COMMON block that I want to SET, which will be accomplished by the ATTNEXIT routine.
There are two exits in this example, the ERRTN and the ATTNEXIT. Should these be coded as subroutines? Should they be internal or external in nature? Is the exit routine meant to encompass IBUF and OUTBUF?
I might be missing something because the example indicates that other processing can be happening at different parts of the code example. I have no idea what this implies.
Joined: 30 Nov 2013 Posts: 917 Location: The Universe
It looks to me you cribbed your example from TSO/E Programming Services. This is OK as far as it goes, but ...
The attention exit is entered as what is called in z/OS an IRB. Basically the PRB running your program is suspended and the IRB for the exit routine is entered. z/OS uses the same scheme to run exits for OPEN. The ERRRTN is not a major issue. You should produce a message showing the error code in register 15 and abandon the idea of using STAX in your run.
You can mess around using OBUF and IBUF but I'm not sure I'd bother.
I have one other program that uses STAX that I no longer use. It potentially does interact with the terminal operator in the attention exit, but it does this using the TPUT and TGET services. This program was written is 1993 and was modernized to run AMODE 31 RMODE ANY in 2007. OBUF and especially IBUF did not meet my requirements in 1993. I think this was a rewrite of something I had done in the 1980s and had lost.
The STAX macro ATTN exit is working after a fashion.
I created a test program to calculate stuff for about a minute. It prints its progress to the screen every second or so.
When I press PA1 to activate the attention exit, nothing happens until the running program finishes filling the screen with its progress reports. Only when the display pauses with "***" at the bottom does the ATTN exit run, indicating so with the "|" and then the program resumes without the user having to so much as touch the keyboard (which is what I wanted). The exit does successfully change the logical flag inside the running program's address space (which is indicated in the progress lines of the running program). Brilliant. But waiting for the screen to fill before responding to the PA1 key, instead of responding immediately, is not the desired effect.
When the PA1 key is pressed, you can see a "T" in the status bar of the 3270 emulator which indicates keystroke(s) in the typeahead buffer.
I'm currently looking into a few current and period TSO programming guides in the hope they can repair my lack of knowledge about the screen-fill delay.
Joined: 30 Nov 2013 Posts: 917 Location: The Universe
You have to be aware there are some environmental conditions where the attention is not immediately processed.
For example, STIMER WAIT,BINTVL==A(500) (5 seconds) the attention will not be processed until the 5 seconds have expired, which is a bit of a surprise. The reason is you're in the STIMER SVC for the 5 seconds and you can't interrupt an SVC.
I'm unsure what is going on with your code. It doesn't sound like there is any reason for the interrupt to be deferred. You may not be checking the flag properly. But that's just a guess.
Anyway, look at this as an example -
Code:
INLOOP CSECT
USING *,12
SAVE (14,12),,*
LR 12,15
LA 15,SAVEAREA
ST 13,4(,15)
ST 15,8(,13)
LR 13,15
LA 2,60
STAX ATTNEXIT
LOOP MVI TIMEFLAG,X'00'
STIMER REAL,ITIMEUP,BINTVL==F'50' (1/2 SECOND)
XLOOP CLI ATTNFLAG,X'FF'
BE EXIT
CLI TIMEFLAG,X'FF'
BNE XLOOP
LA 0,L'MSG
LA 1,MSG
TPUT (1),(0),R
BCT 2,LOOP
B LOOP
EXIT L 13,4(,13)
RETURN (14,12),RC=0
DROP ,
CNOP 0,8
USING *,15
ITIMEUP MVI TIMEFLAG,X'FF'
BR 14
CNOP 0,8
USING *,15
ATTNEXIT MVI ATTNFLAG,X'FF'
BR 14
TIMEFLAG DC X'00'
ATTNFLAG DC X'00'
SAVEAREA DC 9D'0'
LTORG ,
MSG DC C'HELLO'
END INLOOP
The idea is every 1/2 second the program sends HELLO to the terminal until you hit attention, whatever passes for an attention with your emulator.
Code:
call inloop
TEMPNAME ASSUMED AS MEMBERNAME
TEMPNAME ASSUMED AS MEMBERNAME
HELLO
HELLO
HELLO
HELLO
|
READY
This is a proof of concept program; it is not reenterable and is AMODE and RMODE 24.
Joined: 30 Nov 2013 Posts: 917 Location: The Universe
This is slightly more elaborate. Rather than a CPU loop it waits for either an attention or a timer pop, and it writes the time of day in the message.
Code:
INLOOPW CSECT
USING *,12
SAVE (14,12),,*
LR 12,15
LA 15,SAVEAREA
ST 13,4(,15)
ST 15,8(,13)
LR 13,15
LA 2,60
STAX ATTNEXIT
LOOP MVI TIMEECB,X'00'
STIMER REAL,ITIMEUP,BINTVL==F'50' (1/2 SECOND)
XLOOP WAIT 1,ECBLIST=ECBLIST
TM ATTNECB,X'40'
BO EXIT
TM TIMEECB,X'40'
BZ XLOOP
TIME DEC
ST 0,12(,13)
MVC TIME,TPATT
ED TIME,12(13)
MVI TIME,C' '
LA 0,L'MSG
LA 1,MSG
TPUT (1),(0),R
BCT 2,LOOP
B LOOP
EXIT L 13,4(,13)
RETURN (14,12),RC=0
DROP ,
CNOP 0,8
USING *,15
ITIMEUP LR 2,14
POST TIMEECB
BR 2
CNOP 0,8
USING *,15
ATTNEXIT LR 2,14
POST ATTNECB
BR 2
ECBLIST DC A(TIMEECB,X'80000000'+ATTNECB)
TIMEECB DC F'0'
ATTNECB DC F'0'
SAVEAREA DC 9D'0'
LTORG ,
TPATT DC 0C' HH:MM:SS.SS',C'0',X'2120',C':',X'2020',C':',X'2020',>
C'.',X'2020'
MSGX DC C'HELLO'
TIME DC CL(L'TPATT)' '
MSG EQU MSGX,*-MSGX
END INLOOPW
Joined: 30 Nov 2013 Posts: 917 Location: The Universe
I wrote this -
Code:
FORTATTN TITLE 'S T A T T N A N D T S T A T T'
* STATTN and TSTATTN Fortran routines
*
* STATTN start the TSO STAX service
* CALL STATTN
*
* TSATATTN tests if an attention interrupt has been entered
*
* It has been 40 years since I wrote Fortran, so I'm not sure how
* to declare an integer function. Try
*
* INTEGER TSTATT
* CALL STATTN
* 100 IF ( TSTATT( 0 ) .EQ. 0) GO TO 200
* GO TO 100
* 200 STOP
*
* This is based on searching the internet. It was tested using OS/350
* 21.8 Fortran G.
*
* These routines are not reenterable.
*
* STATTN strts the TSO STAX service
*
* TSTATT returns 4 if an attention interrupt has not been detected, or
* 0 if an attention interrupt has been detected. The argument is not
* used or altered.
SPACE 2
FORTATTN CSECT
FORTATTN AMODE 31
FORTATTN RMODE ANY
ENTRY STATTN,TSTATT
STATTN SAVE (14,12),,* SAVE REGISTERS
BALR 12,0 PERPARE STATTN BASE REGISTER
USING *,12 ESTABLISH STATTN ADDRESSABILITY
STAX ATTNEXIT START STAX
RETURN (14,12),RC=0 RESTORE REGISTERS & RETURN
SPACE 2
CNOP 0,8
TSTATT SAVE (14,12),,* SAVE REGISTERS
BALR 12,0 PREPARE TSTATTN BASE REGISTER
USING *,12 ESTABLISH TSTATTN ADDRESSABILITY
LA 0,4 LOAD RETURN CODE
CLI ATTNFLAG,X'FF' ATTENTION INTERRUPT?
BNE *+L'*+2 NO
SR 0,0 LOAD RETURN CODE
ST 0,20(,13) OVERLAY CALLER'S REG 0 WITH RETURN >
CODE
RETURN (14,12),RC=0 RETORE REGISTERS & RETURN
DROP ,
CNOP 0,8
USING *,15 ESTABLISH ATTNEXIT ADDRESSABILITY
ATTNEXIT MVI ATTNFLAG,X'FF' NOTE ATTENTION
BR 14 RETURN TO STAX
ATTNFLAG DC X'00'
END ,
I tested it with this -
Code:
INTEGER TSTATT
CALL STATTN
100 IF ( TSTATT( 0 ) .NE. 0) GO TO 100
STOP
END
The Fortran was compiled with OS/360 21.8 Fortran G compiler & library. It's the only Fortran available to me.
That's interesting. I tested your example code under MVS3.8j. Under TSO, it won't even start unless you first allocate FT05F001 (the terminal) which is unit 5 in Fortran. When you do this and run it in native TSO, you get the same wait-for-screen-full, which in this program never happens. So the terminal is completely locked with no way out but to have an authorized user cancel your UID (no problem in a hardware emulator).
If you want to PRINT to the screen, you must also allocate unit 6 (FT06F001). So I have a CLIST like:
Joined: 30 Nov 2013 Posts: 917 Location: The Universe
mxgdontmics wrote:
I've never used OS/360. Maybe I should for this project!
Well, no. The Fortran compiler & library were taken from OS/360, but the compile and testing were all z/OS. Just for the h*** of it I extracted the IDR data. The compiles were August 1992, which slightly predates z/OS. I did find one compile date in 1978. There may have been more, but the IDR data seems confused.
The first test run I made only required FT06F001, so you probably used a more advanced - well different - Fortran library than me.
That's the same one. If you have access to the CBT Tapes, there's also "Fortran IV H with extensions" and the "H compiler from the Goddard Space Flight Center" (customized by GSFC presumably). In those days, IBM software was virtually open source.
Also there is the WATFIV compiler available.
The H compilers have optimization switches which the G compiler lacks. I'm going to check if they have interrupt extensions. It might be a V8 moment.
Joined: 30 Nov 2013 Posts: 917 Location: The Universe
Jut a couple of notes.
IBM has coding standards programmers must follow. Something like BNE *+6 is strictly forbidden because the use of numbers - like the 6 here - is forbidden.
I think something like
Code:
SIX EQU 6
BNE *+SIX
would pass code review, but I think it is just as bad.
Similarly,
Code:
R2 EQU 2
...
BALR R2,0
USING *,R2
would pass code review, but it's really just as "bad" as
Code:
BALR 2,0
USING *,2
The primary advantage of
R2 EQU 2
is the R2 symbol appears in the symbol XREF table printed by the Assembler. In my opinion, when the RXREF (register XREF) capability was added the the High Level Assembler the need for
R2 EQU 2
disappeared.
HASP for OS/360 had numerous examples of code like this -
Code:
MVI reg,*+L'*+1
MVC X(*-*),Y
Most, if not all, of this type of code was removed from HASP V4 for OS/VS2 Rel 1, and any remaining examples were removed from JES2. Code like that is very bad news for pipelined machines like the z/900 because the pipeline must be flushed and reloaded starting with the altered instruction. Not only that, but in virtual memory machines the page must be stored in the page data set. The code was effectively replaced with
Code:
EX reg,VLINST
...
VLINST MVC X(*-*),Y
This code, too, is bad news on pipelined machines because VLINST must be fetched from storage outside of the pipeline.
Back in the 1960s and 1970s, I was heavily involved with WATFOR/7040 as well as WATFOR/360 and WATFIV. At some point around 1970 or 1971 I installed WATFIV to replace WATFOR/360.
A story I heard about WATFOR/7040 is a special SYSRES tape was prepared with WATFOR being carefully placed just following IBJOB, followed by the linking loader and Fortran (in that order) near the end of the tape. This SYSRES was used to run a batch of WATFOR jobs and similar straight Fortran jobs with some IBM big wigs in attendance. It goes almost without saying the WATFOR jobs ran very quickly, and the regular Fortran jobs ran rather slowly, with lots of movement on the SYSRES tape!
I put a READ statement in the Fortran test program at regular intervals. If the ATTN/PA1 key has been pressed, this is indicated when the next READ occurs, printing the "|" on the screen. However, the ATTN EXIT does not execute until the user replies to the terminal READ. So the program's ATTN exit is at the very bottom of the food chain it seems.
TSO does not necessarily treat a user program as a true command processor. The TSO programming guide suggests that the Fortran program needs to be integrated into a formal TMP (Terminal Monitor Program) which replaces the IBM supplied one, or otherwise functions as a formal command processor. Either of these two are required to setup their own ATTN interrupts among other things.
Or it might be feasible to simply pass-off the Fortran program (with appropriate ATTN exit subroutine) as a replacement TMP at LOGON. But then you have to make sure you can handle the usual TMP housekeeping.
Joined: 30 Nov 2013 Posts: 917 Location: The Universe
Code:
FORTATTN CSECT ESTABLISH FORTATTN CSECT
FORTATTN AMODE ANY
FORTATTN RMODE ANY
ENTRY STATTN,TSTATT
STATTN SAVE (14,2),,* SAVE REGISTERS
BALR 2,0 PERPARE STATTN BASE REGISTER
USING *,2 ESTABLISH STATTN ADDRESSABILITY
STAX ATTNEXIT,MF=(E,STAXPARM) START STAX
RETURN (14,2),RC=0 RESTORE REGISTERS & RETURN
DC 0F'0'
STAXPARM STAX MF=L
DROP 2
SPACE 2
CNOP 0,8
USING *,15 ESTABLISH TSTATTN ADDRESSABILITY
TSTATT LA 0,4 LOAD RETURN CODE
CLI ATTNFLAG,X'FF' ATTENTION INTERRUPT?
BNER 14 RETURN IF NOT
SR 0,0 LOAD RETURN CODE
BR 14 RETURN
DROP ,
CNOP 0,8
USING *,15 ESTABLISH ATTNEXIT ADDRESSABILITY
ATTNEXIT MVI ATTNFLAG,X'FF' NOTE ATTENTION
BR 14 RETURN TO STAX
ATTNFLAG DC X'00'
END ,
Note that TSTATT is radically different, but it works exactly the same as before.
It doesn't save and restore any registers. Other than register 0, it doesn't modify any registers, so why waste CPU clicks saving and restoring registers that are not being modified.
If no attention interrupt has been detected, it executes a total of 3 instructions. The Fortran CALL statement executes more instructions!
There is no program ID. The way it is implemented in the SAVE macro is not good news on a pipelined machine like most modern mainframes.
FORTATTN CSECT ESTABLISH FORTATTN CSECT
FORTATTN AMODE ANY
FORTATTN RMODE ANY
ENTRY STATTN,TSTATT
STATTN SAVE (14,2),,* SAVE REGISTERS
BALR 2,0 PERPARE STATTN BASE REGISTER
USING *,2 ESTABLISH STATTN ADDRESSABILITY
STAX ATTNEXIT,MF=(E,STAXPARM) START STAX
RETURN (14,2),RC=0 RESTORE REGISTERS & RETURN
DC 0F'0'
STAXPARM STAX MF=L
DROP 2
SPACE 2
CNOP 0,8
USING *,15 ESTABLISH TSTATTN ADDRESSABILITY
TSTATT LA 0,4 LOAD RETURN CODE
CLI ATTNFLAG,X'FF' ATTENTION INTERRUPT?
BNER 14 RETURN IF NOT
SR 0,0 LOAD RETURN CODE
BR 14 RETURN
DROP ,
CNOP 0,8
USING *,15 ESTABLISH ATTNEXIT ADDRESSABILITY
ATTNEXIT MVI ATTNFLAG,X'FF' NOTE ATTENTION
BR 14 RETURN TO STAX
ATTNFLAG DC X'00'
END ,
Note that TSTATT is radically different, but it works exactly the same as before.
It doesn't save and restore any registers. Other than register 0, it doesn't modify any registers, so why waste CPU clicks saving and restoring registers that are not being modified.
If no attention interrupt has been detected, it executes a total of 3 instructions. The Fortran CALL statement executes more instructions!
There is no program ID. The way it is implemented in the SAVE macro is not good news on a pipelined machine like most modern mainframes.
STATTN is also different.
Fewer registers are being saved and restored.
The STAX macro uses a remote parameter list.
This is very instructive! Thanks.
Have you been able to test this Fortran/STAX linkage successfully?
Joined: 30 Nov 2013 Posts: 917 Location: The Universe
mxgdontmics wrote:
TSO does not necessarily treat a user program as a true command processor. The TSO programming guide suggests that the Fortran program needs to be integrated into a formal TMP (Terminal Monitor Program) which replaces the IBM supplied one, or otherwise functions as a formal command processor. Either of these two are required to setup their own ATTN interrupts among other things.
Or it might be feasible to simply pass-off the Fortran program (with appropriate ATTN exit subroutine) as a replacement TMP at LOGON. But then you have to make sure you can handle the usual TMP housekeeping.
The interaction between the library I/O routines for something like Fortran and other high level languages (including C 370!) and the user at a TSO terminal is not always very smooth.
In addition, the TSO I/O macros (PUTLINE, PUTGET and GETLINE) anf TSO routines like IKJEFF02 is not always as smooth as one would like. I've been writing TSO command processors for more than 40 years, and just to use the PUTLINE macro, with its multitude of options, requires me to consult the manual every time. Even so, I use only a fraction of what PUTLINE can do. I don't think I've ever even tried PUTGET and GETLINE.
This compiles and links. The one difference here is that I would ordinarily use the LIBRARY IN(FORTAT2) from the OBJECT library instead of INCLUDE SYSLIB(FORTAT2) but the multiple ENTRY statements in your assembly prevented successful link. But I don't fully understand the difference as to why one would use an OBJECT file in one case but a LOAD member in another. I just picked the method that linked without error. But maybe I did something wrong anyway. I don't know.
Next, I make a CLIST. Save in HERC03.TEST.CNTL(STEVETST):
Code:
ALLOC DATASET(*) FILE(FT06F001) SHR
CALL 'HERC03.TEST.LOADLIB(STEVEATN)'
FREE DDNAME(FT06F001)
At the TSO READY prompt:
Code:
EX 'HERC03.TEST.CNTL(STEVETST)'
As with my program, the type-ahead symbol appears in the status bar when pressing PA1, but the program continues to run.
(PA1 executes ATTN on x3270, the emulator I use both at home and at work. Not sure why ATTN does nothing, and I mean NO THING. Mystery.)
This is consistent with the behavior of my test programs (which are printing progress lines to the screen) except mine eventually execute my version of the ATTN exit upon a "***" "screen full" TSO interrupt. The screen-full interrupt "releases" my attention interrupt, but rather late of course.
Maybe I'll post my test assembler/Fortran lashup next.
Joined: 30 Nov 2013 Posts: 917 Location: The Universe
mxgdontmics wrote:
... (PA1 executes ATTN on x3270, the emulator I use both at home and at work. Not sure why ATTN does nothing, and I mean NO THING. Mystery.)...
Perhaps I can provide some insight here.
Real 3270s did not have an ATTN key. In fact, the key labelled as Enter on most keyboards did nothing of the sort. It did do the equivalent of a carriage return line feed within the text buffer in the 3270 controller, but it did nothing to alert the mainframe computer. This fell to keys labeled as PA1, PA2 and (yes) Enter. The Enter key was on the bottom right, roughly where the right Control key is located on most PC keyboards.
The early 3270 emulators from IBM stayed more or less with the 3270 convention. The right Control key became the 3270 Enter key, the PC Enter key was a carriage control line feed as on real 3270s. Many emulators diverted from the 3270 standard over time. Many emulators use the PC Enter key as the primary Enter key. The PC Esc key morphed to the PA1 key in most emulators. Most emulators (including the grossly overpriced IBM emulator) permit some degree of keyboard redefinition. The better ones allow the right Control key to become the 3270 Enter key and the PC Enter key to resume its 3270 definition.
Some years ago I installed the X3270 emulator on my travel laptop and quickly gave up. It works well enough, but the keyboard drove me bonkers. In 2013 when I replaced the 2003 machine that had a decent, though not one of the name brand emulators on it, I went and actually bought the emulator I now use and installed on the 2013 desktop - which is still the main machine and travel laptop. I have carefully retained the install file and just last year successfully installed it on the the only Windoze 10 machine in the house.