IBM Mainframe Forum Index
 
Log In
 
IBM Mainframe Forum Index Mainframe: Search IBM Mainframe Forum: FAQ Register
 

TSO and the STAX Assembler Macro


IBM Mainframe Forums -> PL/I & Assembler
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
mxgdontmics

New User


Joined: 15 Jun 2020
Posts: 27
Location: usa

PostPosted: Mon Jul 13, 2020 11:48 pm
Reply with quote

steve-myers wrote:
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.
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?
Back to top
View user's profile Send private message
steve-myers

Active Member


Joined: 30 Nov 2013
Posts: 917
Location: The Universe

PostPosted: Tue Jul 14, 2020 2:22 am
Reply with quote

mxgdontmics wrote:
Have you been able to test this Fortran/STAX linkage successfully?
Yes, it has been successfully tested using the Fortran program I posted earlier.
Back to top
View user's profile Send private message
steve-myers

Active Member


Joined: 30 Nov 2013
Posts: 917
Location: The Universe

PostPosted: Tue Jul 14, 2020 5:47 am
Reply with quote

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.
Back to top
View user's profile Send private message
mxgdontmics

New User


Joined: 15 Jun 2020
Posts: 27
Location: usa

PostPosted: Tue Jul 14, 2020 11:05 am
Reply with quote

Since I'm testing on a simulated vintage 3033 with 16MB running vintage MVS3.8j, I had to remove the AMODE instructions.


Code:
FORTATTN CSECT                     ESTABLISH FORTATTN CSECT         
         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   ,                 


Assembles fine.
So compile and link the Fortran test program:

Code:
//*********************************************************************
//FORT     EXEC PGM=IEYFORT,REGION=116K                               
//SYSUDUMP DD SYSOUT=A                                                 
//SYSLIN   DD DSN=&&LOADSET,DISP=(MOD,PASS),UNIT=SYSDA,               
//            SPACE=(3200,(57,9),RLSE),DCB=BLKSIZE=3200               
//SYSPRINT DD SYSOUT=A,DCB=(RECFM=FBA,LRECL=120,BLKSIZE=2400)         
//SYSIN    DD *                                                       
      INTEGER TSTATT                                                   
      CALL STATTN                                                     
100   IF ( TSTATT( 0 ) .NE. 0) GO TO 100                               
      STOP                                                             
      END                                                             
//*********************************************************************
//LKED     EXEC PGM=IEWL,REGION=512K,COND=(0,LT,FORT),                 
//         PARM='LIST,LET,XREF'                                       
//STEPLIB  DD DSN=SYS1.LINKLIB,DISP=SHR                               
//SYSUDUMP DD SYSOUT=A                                                 
//SYSLIB   DD DSN=SYS1.FORTLIB,DISP=SHR                               
//         DD DSN=SYS1.COBLIB,DISP=SHR                                 
//         DD DSN=HERC03.TEST.LOADLIB,DISP=SHR                         
//*        DD DSN=SYS1.LOADLIB,DISP=SHR                               
//*        DD DSN=SYSX.LOADLIB,DISP=SHR                               
//SYSLIN   DD DSN=&&LOADSET,DISP=(OLD,DELETE)                         
//         DD DDNAME=SYSIN                                             
//SYSLMOD  DD DSN=HERC03.TEST.LOADLIB,DISP=(MOD,PASS)                 
//SYSPRINT DD SYSOUT=A,DCB=BLKSIZE=3146                               
//SYSUT1   DD DSN=&&SYSUT1,UNIT=(SYSDA,SEP=(SYSLIN,SYSLMOD)),         
//            SPACE=(1024,(200,11))                                   
//IN       DD DSN=HERC03.TEST.OBJ,DISP=SHR                             
//SYSIN    DD *                                                       
  INCLUDE SYSLIB(FORTATT2)                                             
  NAME STEVEATN                                                       


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.
Back to top
View user's profile Send private message
steve-myers

Active Member


Joined: 30 Nov 2013
Posts: 917
Location: The Universe

PostPosted: Tue Jul 14, 2020 4:59 pm
Reply with quote

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.
Back to top
View user's profile Send private message
steve-myers

Active Member


Joined: 30 Nov 2013
Posts: 917
Location: The Universe

PostPosted: Tue Jul 14, 2020 5:18 pm
Reply with quote

Code:
//FORTGCL PROC
//FORT    EXEC PGM=IEYFORT
//STEPLIB  DD  DISP=SHR,DSN=&SYSUID..FORTG.CBT.PDS
//SYSPRINT DD  SYSOUT=*
//SYSLIN   DD  DISP=(,PASS),UNIT=SYSDA,SPACE=(CYL,(1,1)),
//             DCB=(RECFM=FB,LRECL=80,BLKSIZE=3200)
//LINK    EXEC PGM=IEWL,PARM='MAP,XREF,LIST',COND=(0,NE,FORT)
//SYSPRINT DD  SYSOUT=*
//SYSLIB   DD  DISP=(SHR,PASS),DSN=&SYSUID..FORTG.CBT.PDS
//SYSLMOD  DD  DISP=(,PASS),UNIT=SYSDA,SPACE=(CYL,(1,1,1)),
//             DSN=&&GOSET(GO)
//SYSLIN   DD  DISP=(OLD,DELETE),DSN=*.FORT.SYSLIN
//         DD  DDNAME=SYSIN
//        PEND
//A       EXEC PGM=IEFBR14
//LOAD     DD  DISP=(MOD,DELETE),UNIT=SYSALLDA,SPACE=(TRK,0),
//             DSN=&SYSUID..ATTN.LOAD
//B       EXEC FORTGCL,PARM.FORT=LIST
//FORT.SYSIN DD  DISP=SHR,DSN=&SYSUID..ATTN.FORT
//LINK.SYSLMOD DD  DISP=(,CATLG),UNIT=SYSDA,SPACE=(CYL,(1,1,1)),
//             DSN=&SYSUID..ATTN.LOAD(ATTN)
//LINK.SYSIN DD DISP=SHR,DSN=&SYSUID..FORTATTN.OBJ


userid.FORTATTN.OBJ has the object of the Assembler program, which was prepared separately. I got the "assembler" listing just out of curiosity, which actually gave me some insight as to why compiled code differs from Assembler code, which I understood, in part, from earlier analysis, but this code expanded my understanding. To run it, just

call attn.load(attn)

after allocating FT06F001.
Back to top
View user's profile Send private message
mxgdontmics

New User


Joined: 15 Jun 2020
Posts: 27
Location: usa

PostPosted: Thu Jul 16, 2020 10:40 am
Reply with quote

steve-myers wrote:
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.


I used to configure my emulators with the right CNTL key as ENTER until I was forced to use one for awhile where I couldn't figure out how to configure it. I eventually got used to using the PC enter key, with the SHIFT modifier for carriage return and no modifier for ENTER. I never went back to native 3270 key map.

One of the first emulators I got (because I hated the company-supplied one) was QWS3270 by Jolly Gian Software, a one-man shareware company (back then) based in Canada. It was really solid and looked great on the screen. (I just checked and it's still around but wow, really expensive.)

I used to work at <giant defense contractor> in the early 1990s. We had two 3090 600J machines (one of them had the vector facility installed), among other smaller mainframes for test systems and special projects. We even had a CRAY YMP. They ran a lot of NASTRAN on the CRAY and the 600J vector machine.

My job was in computer measurement and capacity planning. I used a 3179G terminal (graphics capable). But we also had the older 60 pound 3270 terminals that could also do graphics (blue lightning included) and some other 31xx terminals that did just green screen.

The keyboards for the 31xx models looked like a souped-up IBM PC keyboards, with 24 PF-keys in two rows across the top, 2 columns of miscellaneous keys at the far left, which included the ATTN key in the upper left column, and the standard PC arrow key cluster to the right and above those were the 3270-specific PA1...etc, keys. I even think this one had a 10-key cluster at the far right.

Seems like the ALT/ATTN key combo would get you out of some lockups where the PA1 key would not. But my memory may be faulty.

Sometimes I had to use the old 3270 terminals which had a unique keyboard feel and compact layout. A lot of people really preferred those. Practically needed a forklift to move them around though.
Back to top
View user's profile Send private message
steve-myers

Active Member


Joined: 30 Nov 2013
Posts: 917
Location: The Universe

PostPosted: Thu Jul 16, 2020 12:55 pm
Reply with quote

I used the 31xx terminal for a while. I agree the keyboard appeared to be based on the IBM PC keyboard. Those were the days when IBM was at its best in many ways reusing technology. Few people recall, any more, that the keyboard for the 360/85, 370/165 and 370/168 graphic console (5450 for the /85, 3066 for the /165 and /168) was based on the keypunch keyboard! The 2540 reader-punch, a work horse on 360 and 370 machines, was based on the 1402 reader punch from the 1401, and the 1402, in turn, was based on an EAM machine from the 1950s.

I also used 3277 terminals for a while back in the 1970s. Provided it was channel attached it was a superb TSO terminal. Line attached, even at 9600 BPS, it wasn't a great TSO terminal, especially with SPF. For all that SPF did a great job compressing its screens, it still took too long to send a screen, even at 9600 BPS. Dropping multiple 3270s on a single 9600 BPS line, well, you could take naps waiting for screen updates. As an operator console it kind of sucked: the keyboard seemed to lock while data was being sent to the screen, which was all the time with an operator console. Still it was better than a 2260!

My employer was one of the first to get 3270s. We even had one catch fire on us!

I agree Jolly Giant has gotten awful damn greedy, though QWS3270 is a pretty decent emulator.

You can still get 24 function key keyboards fron Unicomp, though I don't know about emulator support. I'll probably try one of their regular keyboards when my present Cherry keyboard goes to keyboard heaven (or hell?) The keyboards sent out with just about all new machines su** big time
Back to top
View user's profile Send private message
mxgdontmics

New User


Joined: 15 Jun 2020
Posts: 27
Location: usa

PostPosted: Thu Jul 16, 2020 8:30 pm
Reply with quote

These days I configure my emulator as a 3290 single-display at 160×62. I love that amount of real-estate. You need a big monitor though (especially as I get older). I used to lust after the original amber plasma ones at <giant defense, inc.>. The engineers used them configured with 4 3278 screens to monitor all the LPARS, which was handy.
Back to top
View user's profile Send private message
mxgdontmics

New User


Joined: 15 Jun 2020
Posts: 27
Location: usa

PostPosted: Thu Jul 16, 2020 10:33 pm
Reply with quote

steve-myers wrote:
Code:
//FORTGCL PROC
//FORT    EXEC PGM=IEYFORT
//STEPLIB  DD  DISP=SHR,DSN=&SYSUID..FORTG.CBT.PDS
//SYSPRINT DD  SYSOUT=*
//SYSLIN   DD  DISP=(,PASS),UNIT=SYSDA,SPACE=(CYL,(1,1)),
//             DCB=(RECFM=FB,LRECL=80,BLKSIZE=3200)
//LINK    EXEC PGM=IEWL,PARM='MAP,XREF,LIST',COND=(0,NE,FORT)
//SYSPRINT DD  SYSOUT=*
//SYSLIB   DD  DISP=(SHR,PASS),DSN=&SYSUID..FORTG.CBT.PDS
//SYSLMOD  DD  DISP=(,PASS),UNIT=SYSDA,SPACE=(CYL,(1,1,1)),
//             DSN=&&GOSET(GO)
//SYSLIN   DD  DISP=(OLD,DELETE),DSN=*.FORT.SYSLIN
//         DD  DDNAME=SYSIN
//        PEND
//A       EXEC PGM=IEFBR14
//LOAD     DD  DISP=(MOD,DELETE),UNIT=SYSALLDA,SPACE=(TRK,0),
//             DSN=&SYSUID..ATTN.LOAD
//B       EXEC FORTGCL,PARM.FORT=LIST
//FORT.SYSIN DD  DISP=SHR,DSN=&SYSUID..ATTN.FORT
//LINK.SYSLMOD DD  DISP=(,CATLG),UNIT=SYSDA,SPACE=(CYL,(1,1,1)),
//             DSN=&SYSUID..ATTN.LOAD(ATTN)
//LINK.SYSIN DD DISP=SHR,DSN=&SYSUID..FORTATTN.OBJ


userid.FORTATTN.OBJ has the object of the Assembler program, which was prepared separately. I got the "assembler" listing just out of curiosity, which actually gave me some insight as to why compiled code differs from Assembler code, which I understood, in part, from earlier analysis, but this code expanded my understanding. To run it, just

call attn.load(attn)

after allocating FT06F001.


Interesting that this works fine under z/OS TSO. Under MVS3.8j/TSO, it behaves as I described earlier. I use z/OS at work, but it's not appropriate to do these tests there, even on our test system.

This research is for a personal hobby project. It's a period (circa 1977) Fortran program that originally ran on a Xerox Sigma 9 which I think was somewhat comparable to an s360, i.e. EBCDIC, big-endian, 32-bit, etc. I'm using a period, simulated IBM 3033 running MVS3.8j. There is a turnkey solution for simulating this platform, which is already loaded with the compilers needed for Fortran IV. I thought this might be an easy port, which is proving to be true for the Fortran code and the TOD assembler subroutine. If I can solve the TSO/ATTN issue, real testing can begin on the actual program, which is a sophisticated piece of software (8500 lines of Fortran).

The evolution of MVS/TSO since those days must hold the reason why execution results for TSO ATTN interruption are not the same.
Back to top
View user's profile Send private message
mxgdontmics

New User


Joined: 15 Jun 2020
Posts: 27
Location: usa

PostPosted: Fri Jul 17, 2020 2:08 am
Reply with quote

steve-myers wrote:
Code:
//FORTGCL PROC
//FORT    EXEC PGM=IEYFORT
//STEPLIB  DD  DISP=SHR,DSN=&SYSUID..FORTG.CBT.PDS
//SYSPRINT DD  SYSOUT=*
//SYSLIN   DD  DISP=(,PASS),UNIT=SYSDA,SPACE=(CYL,(1,1)),
//             DCB=(RECFM=FB,LRECL=80,BLKSIZE=3200)
//LINK    EXEC PGM=IEWL,PARM='MAP,XREF,LIST',COND=(0,NE,FORT)
//SYSPRINT DD  SYSOUT=*
//SYSLIB   DD  DISP=(SHR,PASS),DSN=&SYSUID..FORTG.CBT.PDS
//SYSLMOD  DD  DISP=(,PASS),UNIT=SYSDA,SPACE=(CYL,(1,1,1)),
//             DSN=&&GOSET(GO)
//SYSLIN   DD  DISP=(OLD,DELETE),DSN=*.FORT.SYSLIN
//         DD  DDNAME=SYSIN
//        PEND
//A       EXEC PGM=IEFBR14
//LOAD     DD  DISP=(MOD,DELETE),UNIT=SYSALLDA,SPACE=(TRK,0),
//             DSN=&SYSUID..ATTN.LOAD
//B       EXEC FORTGCL,PARM.FORT=LIST
//FORT.SYSIN DD  DISP=SHR,DSN=&SYSUID..ATTN.FORT
//LINK.SYSLMOD DD  DISP=(,CATLG),UNIT=SYSDA,SPACE=(CYL,(1,1,1)),
//             DSN=&SYSUID..ATTN.LOAD(ATTN)
//LINK.SYSIN DD DISP=SHR,DSN=&SYSUID..FORTATTN.OBJ


userid.FORTATTN.OBJ has the object of the Assembler program, which was prepared separately. I got the "assembler" listing just out of curiosity, which actually gave me some insight as to why compiled code differs from Assembler code, which I understood, in part, from earlier analysis, but this code expanded my understanding. To run it, just

call attn.load(attn)

after allocating FT06F001.


If you had 2 assembler subroutines to link, would you concatenate the OJB files?
Back to top
View user's profile Send private message
steve-myers

Active Member


Joined: 30 Nov 2013
Posts: 917
Location: The Universe

PostPosted: Fri Jul 17, 2020 4:32 am
Reply with quote

mxgdontmics wrote:
If you had 2 assembler subroutines to link, would you concatenate the OJB files?
That's one way of doing it. Another way is to put them into a Link edit SYSLIB data set and put the data set into the Link edit SYSLIB DD statement.

Since this was just an experiment, I did it the simplest and most obvious way.

I do have a few library type routines. Lately I haven't been using them, but I use SYSLIB when I do use them. See CBT files 956 or another one I couldn't quickly find.
Back to top
View user's profile Send private message
mxgdontmics

New User


Joined: 15 Jun 2020
Posts: 27
Location: usa

PostPosted: Thu Aug 06, 2020 12:04 am
Reply with quote

I ran a test on z/OS where I work. The STAX exit behaves the same as on the MVS3.8j system under Hercules. The PA1 is queued in the type-ahead buffer until a screen-full (***) or a TGET from the program occurs. I don't know how to get around this.

Is it an artifact of running 3270 over Telnet?
Back to top
View user's profile Send private message
mxgdontmics

New User


Joined: 15 Jun 2020
Posts: 27
Location: usa

PostPosted: Fri Aug 07, 2020 2:19 am
Reply with quote

steve-myers wrote:
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
Sample run
Code:
call inloopw(tempname)
 HELLO 12:34:27.25   
 HELLO 12:34:27.75   
 HELLO 12:34:28.25   
 HELLO 12:34:28.76   
 HELLO 12:34:29.26   
 HELLO 12:34:29.76   
 HELLO 12:34:30.26   
 HELLO 12:34:30.76   
 HELLO 12:34:31.27   
 HELLO 12:34:31.77   
 HELLO 12:34:32.27   
 HELLO 12:34:32.77   
 HELLO 12:34:33.27   
 HELLO 12:34:33.77   
 |                   
 READY


Even your clear example here queues the PA1 in the type-ahead buffer until the screen becomes full of "HELLO" and the "***" appears. Only then does the interrupt manifest itself. So if one's program isn't doing any screen filling, it will simply never receive the PA1 unless and until a READ/TGET is executed.

Maybe this is a problem with the 3270 emulator. All of the x3270/c3270 emulators work the same way. Even if you toggle "aidWait" which is supposed to change the behavior of terminal commands like ENTER, PA1, etc., the keys marked with an * in the documentation (ENTER, PA1, etch.) all say that these keys are queued in the type-ahead "until the terminal is unlocked". "aidWait" disabled throws the handling of these key presses to whatever emulator macro (user-written presumably) might be coded to address them under a "terminal locked" condition.

I looked at the documentations for PCOMM, Vista and QWS emulators, all of which say they support type-ahead, but I don't know if it can be disabled or if it is even the problem to begin-with.

None of the vintage nor current TSO application programming guides talk about there being any kind of problems like this. If you use STAX, your program is PA1-interruptible and that's it. No pitfalls or problems like this are mentioned anywhere.
Back to top
View user's profile Send private message
steve-myers

Active Member


Joined: 30 Nov 2013
Posts: 917
Location: The Universe

PostPosted: Fri Aug 07, 2020 4:48 am
Reply with quote

Well, when I ran it, the screen shot in the post is exactly what I got. Exactly. Are you 100% certain you replicated the program as listed, with the POST macro (for its own ECB) in each exit? I ask this because you had mentioned at least one of the exits you coded as just BR 14.

You mentioned, too, that you removed the AMODE and RMODE statements from the Assembler functions you ran with your Fortran program. I put them there because I assumed you would be using it with a modern Fortran that compiles & links with AMODE 31 / RMODE ANY. With an OS/360 Fortran its moot as the object (and load module) default to AMODE 24 / RMODE 24. The Assembler code is actually AMODE ANY / RMODE ANY.
Back to top
View user's profile Send private message
mxgdontmics

New User


Joined: 15 Jun 2020
Posts: 27
Location: usa

PostPosted: Fri Aug 07, 2020 10:31 am
Reply with quote

steve-myers wrote:
Well, when I ran it, the screen shot in the post is exactly what I got. Exactly. Are you 100% certain you replicated the program as listed, with the POST macro (for its own ECB) in each exit? I ask this because you had mentioned at least one of the exits you coded as just BR 14.

You mentioned, too, that you removed the AMODE and RMODE statements from the Assembler functions you ran with your Fortran program. I put them there because I assumed you would be using it with a modern Fortran that compiles & links with AMODE 31 / RMODE ANY. With an OS/360 Fortran its moot as the object (and load module) default to AMODE 24 / RMODE 24. The Assembler code is actually AMODE ANY / RMODE ANY.


Apologies for any confusion. I actually replied to your second INLOOP example when I actually tested the first INLOOP example.

I was backtracking through the discussion to see if I missed anything and became interested in your TIMER interrupt example. I wondered if an internal interrupt would somehow bring the program up for air (so to speak) to allow the external interrupt (PA1) to be detected.

I copied and assembled your code verbatim which contained no explicit AMODE/RMODE directives.

The assembly output on MVS3.8j is identical to the assembly on z/OS (02.02.00). For each test I used the x3270 emulator. The behavior of the program on both platforms is identical.

INLOOP begins printing "HELLO" down the screen. When I press PA1, it continues printing "HELLO" but you can see the "T" in the status bar of the 3270 emulator, indicating that the PA1 key press went into the type-ahead buffer. Once the screen becomes full of the "HELLO" messages, the screen full symbol is printed (***) after which the screen refreshes without pressing the ENTER key. Immediately the "|" interrupt symbol prints and then immediately, READY. Program done.

Without any real understanding of what is happening, I'm inclined to suspect my 3270 emulator. But I don't really know. This doesn't seem to be happening when you run INLOOP.
Back to top
View user's profile Send private message
mxgdontmics

New User


Joined: 15 Jun 2020
Posts: 27
Location: usa

PostPosted: Sat Aug 08, 2020 4:32 am
Reply with quote

After some communication with the code maintainer for the x3270 family of emulators, it was determined that the actual labeled ATTN key works under z/OS (with Steve's INLOOP program). But under MVS3.8j, it does nothing (as mentioned before), but then neither do the PA keys when using the x3270 emulator. One would assume it's because MVS3.8j predates the advent of terminal keyboards that featured the ATTN key. Prior to that, an attention key was a PA key (1-3).

The early IBM TSO guides to writing terminal monitor programs and command processors (circa 1972, 1985), which can be found on the internet, only talk about the necessity for establishing exits when the user presses "the attention key". The actual key names (PA1, etc.) are never mentioned.

But the latest version of this guide says, "the PA1 or attention key". So when MVS3.8j was the latest thing, the PA keys were the attention keys (as Steve has already said). But x3270 doesn't treat them as attention keys, only the ATTN key itself.

I don't imagine that IBM has changed the status of the PA keys in all this time, but the code maintainer did say that, "The 3270 programmer's reference is more a collection of hints than a reference."

I did mention to the maintainer that anecdotal information suggested that other emulators behaved differently regarding the PA keys, e.g. Steve has no trouble with the PA key interrupting the code examples in this thread.
Back to top
View user's profile Send private message
steve-myers

Active Member


Joined: 30 Nov 2013
Posts: 917
Location: The Universe

PostPosted: Sat Aug 08, 2020 8:01 am
Reply with quote

mxgdontmics wrote:
...
The early IBM TSO guides to writing terminal monitor programs and command processors (circa 1972, 1985), which can be found on the internet, only talk about the necessity for establishing exits when the user presses "the attention key". The actual key names (PA1, etc.) are never mentioned.
OS/360 TSO was designed for teleprinter terminals. The IBM 2741, in other words. The 2741 DID have an attention key. The 3270 was just a dream in 1970, though some 2260 models were supported. I remember using a 2260 with TSO, very vaguely. It was much like the 3270. I do not recall how to do an attention.

The z/OS manuals are very similar to the MVT manuals. In fact you can take an OS/360 command processor assembled with the OS/360 macros and the command processor will run on z/OS, possibly slower because you use LINK rather than CALLTSSR to run IKJPARS, and macros like PUTLINE use the LINK macro to call the service routine; the z/OS macros use the equivalent of CALLTSSR to run the service routine. In fact you can take the same source code, reassemble it with z/OS macros, and the command will run OK. Unless there are other AMODE/RMODE issues, a command processor assembled with OS/360 macros will not run AMODE 31 RMODE ANY, but the same code assembled with z/OS macros will run AMODE 31 / RMODE ANY. The PCL uses 4 byte internal adcons in z/OS, where it uses 3 byte adcons in MVT. I know. I've tried it.
Back to top
View user's profile Send private message
mxgdontmics

New User


Joined: 15 Jun 2020
Posts: 27
Location: usa

PostPosted: Sun Aug 09, 2020 4:51 am
Reply with quote

steve-myers wrote:
mxgdontmics wrote:
...
The early IBM TSO guides to writing terminal monitor programs and command processors (circa 1972, 1985), which can be found on the internet, only talk about the necessity for establishing exits when the user presses "the attention key". The actual key names (PA1, etc.) are never mentioned.
OS/360 TSO was designed for teleprinter terminals. The IBM 2741, in other words. The 2741 DID have an attention key. The 3270 was just a dream in 1970, though some 2260 models were supported. I remember using a 2260 with TSO, very vaguely. It was much like the 3270. I do not recall how to do an attention.

The z/OS manuals are very similar to the MVT manuals. In fact you can take an OS/360 command processor assembled with the OS/360 macros and the command processor will run on z/OS, possibly slower because you use LINK rather than CALLTSSR to run IKJPARS, and macros like PUTLINE use the LINK macro to call the service routine; the z/OS macros use the equivalent of CALLTSSR to run the service routine. In fact you can take the same source code, reassemble it with z/OS macros, and the command will run OK. Unless there are other AMODE/RMODE issues, a command processor assembled with OS/360 macros will not run AMODE 31 RMODE ANY, but the same code assembled with z/OS macros will run AMODE 31 / RMODE ANY. The PCL uses 4 byte internal adcons in z/OS, where it uses 3 byte adcons in MVT. I know. I've tried it.


RESOLVED

The software context of the problem in this thread was the use of the x3270-family of terminal emulators (x3270, c3270, ws3270, wx3270, etc.) and TSO on the operating systems, z/OS_2.2 on a z/Series mainframe and MVS3.8j under Hercules emulation. Also, the free trial version of QWS3270 was tested to help rule out possible issues with x3270.

The resolution is as follows:
    For contemporary versions of z/OS, the ATTN key works with STAX attention exits. The PA keys (program attention keys, PA1, PA2, etc.) do not work to provide asynchronous program attention interruption, even in combination with RESET.

    For legacy MVS that predates the standardization of the ATTN key on 3270 keyboards (e.g. MVS3.8j circa 1981), PA (program attention) keys would seem to be the only option (PA1, PA2, etc).

    On the aforementioned version of legacy MVS, The PA keys will only work by themselves (without any other key involved) AFTER the problem-mode program initiates a terminal read (TGET) OR the program fills the screen with output, initiating a screen-full attention (***). Pending either of those two events, PA key activations will languish in the type-ahead buffer of the terminal emulator.

    RESOLUTION: For asynchronous attention activations to work on legacy MVS, PA key activation (e.g. PA1) must be prefaced by the RESET key (RESET then PA1). Only with the RESET-PA1 sequence will the attention exit be activated asynchronously in the same way that the ATTN key works on z/OS.


As mentioned already, this behavior was tested on x3270-family emulators AND the free trial version of QWS3270 5.1 (Jolly Giant Software).

Thanks to steve-meyers for his patience and highly instructive code examples that vastly increased my understanding of the issue, and to x3270 code maintainer, Paul Mattes, for suggesting the solution to this problem.

P.S. This may not be the only possible solution for this issue, it's just "a solution". One question suggests itself: Did say, a period 3277 terminal user have to use the RESET-PA1 key sequence to do program interrupts?
Back to top
View user's profile Send private message
steve-myers

Active Member


Joined: 30 Nov 2013
Posts: 917
Location: The Universe

PostPosted: Mon Aug 10, 2020 9:54 pm
Reply with quote

mxgdontmics wrote:
... Did say, a period 3277 terminal user have to use the RESET-PA1 key sequence to do program interrupts?
To tell the truth, I'm no longer certain about my statement that 3270 keyboards did not have an ATTN key. While I could not find a clear picture on the net, at the top of the column of keys on the left side the keyboard a key does seem to be labeled ATTN.

For a brief period of time during my time with a <large defense contractor> I used a 3270 PC with the 24 function key keyboard. In fact it was my first time with a directly attached PC based emulator although I had used a couple of dialup emulators in the 1980s. This was '90 / '91 and maybe into '92 or even '93. Subsequently I used several IBM emulators with coax based LAN and OS/2. Very late I used the PCOMM emulator bundled into OS/2 Warp 4 with TCPIP. Then the <large defense contractor> sold most of us mainframe types off to IBM who fired most of us after about 18 months.

The COAX based emulators saved my b*** one day when the MVS IP stack broke and I was one of the few people that could still get into TSO to look over things.
Back to top
View user's profile Send private message
mxgdontmics

New User


Joined: 15 Jun 2020
Posts: 27
Location: usa

PostPosted: Mon Aug 10, 2020 10:50 pm
Reply with quote

steve-myers wrote:
mxgdontmics wrote:
... Did say, a period 3277 terminal user have to use the RESET-PA1 key sequence to do program interrupts?
To tell the truth, I'm no longer certain about my statement that 3270 keyboards did not have an ATTN key. While I could not find a clear picture on the net, at the top of the column of keys on the left side the keyboard a key does seem to be labeled ATTN.

For a brief period of time during my time with a <large defense contractor> I used a 3270 PC with the 24 function key keyboard. In fact it was my first time with a directly attached PC based emulator although I had used a couple of dialup emulators in the 1980s. This was '90 / '91 and maybe into '92 or even '93. Subsequently I used several IBM emulators with coax based LAN and OS/2. Very late I used the PCOMM emulator bundled into OS/2 Warp 4 with TCPIP. Then the <large defense contractor> sold most of us mainframe types off to IBM who fired most of us after about 18 months.

The COAX based emulators saved my b*** one day when the MVS IP stack broke and I was one of the few people that could still get into TSO to look over things.


I could not find an ATTN key on this image of a 3277.

vintagecomputer.ca/wp-content/uploads/2017/02/IBM-3277-terminal-profile.jpg

The first terminal I could find with an ATTN key is the 3278 which was introduced in 1980. MVS 3.8, where the ATTN key seems to be ignored under TSO, was introduced ~1981.
Back to top
View user's profile Send private message
steve-myers

Active Member


Joined: 30 Nov 2013
Posts: 917
Location: The Universe

PostPosted: Tue Aug 11, 2020 6:23 am
Reply with quote

Your 3270 image is the best I've seen. I agree the top left key does not seem to say ATTN. It might even say Clear! I had access to a real 3290 from 2000 through 2007, but never once used it.

I think MVS 3.8 might have been earlier than '81. By then the TCAM based TSO was pretty much history; we had switched to TSOVTAM by the late 1970s. I don't know whether your MVS 3.8 uses VTAM or TCAM. Prejudice says TCAM, but I don't know. I think VTAM was always an addon, but I don't know. If it is an addon, then it likely is not in the free 3.8.
Back to top
View user's profile Send private message
mxgdontmics

New User


Joined: 15 Jun 2020
Posts: 27
Location: usa

PostPosted: Tue Aug 11, 2020 8:11 am
Reply with quote

MVS3.8j can use both (default is VTAM) but I don't know how much it has been modified or enhanced to bring it back alive. A lot of software has been written to reverse-engineer non-public-domain features. There are two SPF-like options that are very nice, for example. The SPF editor is an excellent work-alike.
Back to top
View user's profile Send private message
hankoerlemans

New User


Joined: 25 Jan 2018
Posts: 57
Location: Australia

PostPosted: Mon Sep 21, 2020 11:53 am
Reply with quote

Hi guys,
not sure if you've resolved this but please take a look at the CLSTATTN operand of the STAX macro.
Trying to wade through doc and memories from 2004 but I think the gist of it is that your application STAX needs to be at the top of the pile using this parm.
Otherwise you are at the mercy of whatever CLIST, TSO and ISPF processing has occurred before your program has even loaded - let alone received control.
Hope that's of use.

Hank
Back to top
View user's profile Send private message
View previous topic :: :: View next topic  
Post new topic   Reply to topic View Bookmarks
All times are GMT + 6 Hours
Forum Index -> PL/I & Assembler Goto page 1, 2  Next

 


Similar Topics
Topic Forum Replies
No new posts PRINTOUT macro PL/I & Assembler 0
No new posts Build dataset list with properties us... PL/I & Assembler 4
No new posts Finding Assembler programs PL/I & Assembler 5
No new posts How Can I Recall a Migrated Data Set ... PL/I & Assembler 3
No new posts create rexx edit Macro that edits the... CLIST & REXX 3
Search our Forums:

Back to Top