Help with LH and AR instructions



High Level Assembler(HLASM) for MVS & VM & VSE

Help with LH and AR instructions

Postby ramkumar1992sp » Thu Dec 08, 2016 12:13 pm

Hello,

I have a two tables as defined below.My COBOL program is passing these two while calling an Assembler program.


01 ASSGND-DAYS.
05 FILLER OCCURS 050 TIMES PIC X(2).

01 MEETING-TABLE SYNCHRONIZED.
   05 MT-TABLE-ENTRY OCCURS 1000 TIMES INDEXED BY MT-X1.
      10 MT-SEM-DAYS PIC X(2).
      10 MT-PERIODS.
         15 MT-PER-FR PIC S9(4) COMP-4.
         15 MT-PER-TO PIC S9(4) COMP-4.
 


R1 Register points to ASSGND-DAYS table/array and R2 Points to MEETING-TABLE.

I have the below code in my Assembler program.


GETSEM   LH    R5,2(R2)                   LOAD START PER OF MT ENTRY    
              AR    R5,R1                            ADD ARRAY ADDR    
 


LH will load the contents(half word) of R2 from a displacement of 2.Therefore the contents of MT-PER-FR will be loaded to R5.

Lets say MT-PER-FR has a value of +04.So now R5 will have 0004.

with AR R5,R1 We are adding the contents of R1 i.e R1 has the address of ASSGND-DAYS array to R5.

Why are they doing this ? Is this how they point R5 to MT-PER-FR ?


Thanks
ramkumar1992sp
 
Posts: 71
Joined: Sat Jul 23, 2016 8:52 am
Has thanked: 40 times
Been thanked: 0 time

Re: Help with LH and AR instructions

Postby ramkumar1992sp » Thu Dec 08, 2016 7:34 pm

I m sorry.I think R5 nows to points to ASSGND-DAYS ARRAY but I dont know why we are doing a LH R5,2(R2) and then adding the address.
ramkumar1992sp
 
Posts: 71
Joined: Sat Jul 23, 2016 8:52 am
Has thanked: 40 times
Been thanked: 0 time

Re: Help with LH and AR instructions

Postby Robert Sample » Thu Dec 08, 2016 7:53 pm

I dont know why we are doing a LH R5,2(R2) and then adding the address.
We don't either. You would need to post a lot more of the assembler code for us to figure out what it is doing. If, as you say, R1 points to ASSGND-DAYS and R2 points to MEETING-TABLE then the code you posted makes no sense at all.
Robert Sample
Global moderator
 
Posts: 3719
Joined: Sat Dec 19, 2009 8:32 pm
Location: Dubuque, Iowa, USA
Has thanked: 1 time
Been thanked: 279 times

Re: Help with LH and AR instructions

Postby ramkumar1992sp » Thu Dec 08, 2016 8:12 pm

Hello,
This is the complete program and the parm list that are passed through XXXQVLST is below the code.Can you please help with the LH and AR instructions part?

       PUNCH '      ALIAS  XXXQ71S2'                                  00001100
XXXQ71S1 START 0                                                        00001200
         ENTRY XXXQ71S2                                                 00001300
         EXTRN XXXQVLST                                                 00001400
         USING *,15                                                     00001500
         B     COIBMEND                                                 00001600
*                                                                       00001700

*                                                                       00002000
R0       EQU   0                                                        00002100
R1       EQU   1                            ADDR OF STUDENT ARRAY --    00002200
*                                               ASSIGNED DAYS           00002300
R2       EQU   2                            ADDR OF MEETING TIME TABLE  00002400
R3       EQU   3                            ADDR OF LOOP CONTROL DATA   00002500
R4       EQU   4                            ADDR OF CLASS RECORD        00002600
R5       EQU   5                                                        00002700
R6       EQU   6                                                        00002800
R7       EQU   7                                                        00002900
R8       EQU   8                                                        00003000
R9       EQU   9                                                        00003100
RA       EQU   10                                                       00003200
RB       EQU   11                                                       00003300
RC       EQU   12                           BR REG FOR BIT OPERATION    00003400
RD       EQU   13                                                       00003500
RE       EQU   14                           BR REG FOR NEXT INSTRUCTION 00003600
RF       EQU   15                                                       00003700
*                                                                       00003800
COIBMEND EQU   *                                                        00003900
         SAVE  (14,12)                                                  00004000
         L     RA,=A(XXXQVLST)              LOAD ADDR OF PARAMETER LIST 00004100
         LM    R1,R4,0(RA)                                              00004200
         LA    RF,XXXQ71S2                                              00004300
         USING XXXQ71S2,RF                                              00004400
         LA    RC,TESTBITS                  POINT BR REG TO TM INST     00004500
         LA    RE,ASGNBITS                                              00004600
         B     STARTOP                                                  00004700
XXXQ71S2 SAVE  (14,12)                                                  00004800
         L     RA,=A(XXXQVLST)              LOAD ADDR OF PARAMETER LIST 00004900
         LM    R1,R4,0(RA)                                              00005000
         LA    RC,XORBITS                   POINT BR REQ TO XOR INST    00005100
         LA    RE,RETURNIT                                              00005200
STARTOP  LA    R6,1                         R6 = CONSTANT 1             00005300
         LH    R8,2(R3)                     LOAD LAST SEM BIT VALUE     00005400
         AR    R8,R6                           INCR LAST VALUE BY 1     00005500
         LH    RA,0(R3)                        LOAD FIRST SEM BIT VALUE 00005600
         SR    R8,RA                           SUBT FIRST FROM LAST     00005700
         STH   R8,HLDSEMS                   SAVE NUMB SEMS TO BE        00005800
*                                               PROCESSED               00005900
*                                                                       00006000
*                                                                       00006100
*                                  INIT SUBROUTINE FOR EACH BIT OPER    00006200
*                                                                       00006300
INIT     LH    RB,12(R4)                    LOAD INDEX TO MT TABLE      00006400
*                                               ENTRY                   00006500
         MH    RB,SIX                           MULT INDEX BY SIX       00006600
         AR    RB,R2                            ADD ADDR OF MT TABLE    00006700
         LH    R0,14(R4)                    LOAD NUMB OF MT ENTRIES     00006800
*                                                                       00006900
*                                  PROCESS EACH MT ENTRY CLASS MEETS    00007000
*                                                                       00007100
NEWMEET  MVC   TESTBITS+1(1),1(RB)          INSERT DAYS MET IN BIT      00007200
*                                               INSTRUCTIONS            00007400
         MVC   ORBITS+1(1),1(RB)                                        00007400
         MVC   XORBITS+1(1),1(RB)                                       00007500
         LH    R8,HLDSEMS                   R8 = NUMD SEMS TO PROCESS   00007600
         LH    RA,0(R3)                                                 00007700
         IC    R9,0(RB)                     INSERT SEM BITS IN REG 9    00007800
         SLL   R9,23(RA)                        SHIFT TO FIRST SEM BIT  00007900
         LR    RA,R1                        LOAD ADDR OF STUDN ARRAY    00008000
         LH    R7,4(RB)                     LOAD END PER OF MT ENTRY    00008100
         AR    R7,RA                            ADD ARRAY ADDR          00008200
*                                                                       00008205
*                                  PROCESS EACH SEM MT ENTRY MEETS      00008210
*                                                                       00008215
GETSEM   LH    R5,2(RB)                   LOAD START PER OF MT ENTRY    00008220
         AR    R5,RA                            ADD ARRAY ADDR          00008225
         SLL   R9,1                         SHIFT SEM BIT TO SIGN       00008230
*                                               POSITION                00008235
         LTR   R9,R9                       TEST SEM BIT VALUE           00008240
         BZ    NEXTMEET                         NO SEM BITS LEFT        00008245
         BP    NEXTSEM                          SEM BIT = 0             00008250
*                                                                       00008300
*                                  PROCESS ALL PERIODS FOR EACH SEM     00008400
*                                                                       00008500
PERLOOP  BR    RC                           BRANCH TO BIT INSTRUCTIONS  00008600
*                                           TESTBITS - CHECK CONFLICTS  00008605
*                                           ORBITS - ASSIGN SECTION     00008610
*                                           XORBITS - UNASSIGN SECTION  00008615
TESTBITS TM    0(R5),X'00'                  TEST ARRAY FOR CONFLICT     00008700
         BC    5,SETCONFL                                               00008800
LOOPCTL  BXLE  R5,R6,PERLOOP                INCR TO NEXT PERIOD         00008900
*                                                                       00009000
*                                  INCR TO NEXT SEM MT ENTRY MEETS      00009100
*                                                                       00009200
NEXTSEM  AH    RA,4(R3)                                                 00009300
         AH    R7,4(R3)                                                 00009400
         BCT   R8,GETSEM                    ARE ALL SEMESTERS PROCESSED 00009500
*                                                                       00009600
*                                  INCR TO NEXT MT ENTRY CLASS MEETS    00009700
*                                                                       00009800
NEXTMEET AH    RB,SIX                                                   00009900
         BCT   R0,NEWMEET                   ARE ALL MT ENTRIES PROCESSD 00010000
         BR    RE                                                       00010100
SETCONFL MVI   16(R4),C'Y'                  TURN ON CONFLICT SWCH       00010200
RETURNIT RETURN (14,12),RC=0                RETURN TO MAIN LINE     1-5 00010300
*                                                                       00010400
*                                  PROCESS NON CONFLICTING CLASS        00010500
*                                                                       00010600
ASGNBITS LA    RC,ORBITS                    POINT BR REG TO OR INSTR    00010700
         LA    RE,RETURNIT                                              00010800
         B     INIT                                                     00010900
ORBITS   OI    0(R5),X'00'                  ASSIGN MT ENTRY TO STUDN    00011000
*                                               ARRAY                   00011100
         B     LOOPCTL                                                  00011200
*                                                                       00011300
*                                  BACK OUT PERVIOUS ASSIGNMENTS        00011400
*                                                                       00011500
XORBITS  XI    0(R5),X'00'                  UNASSIGN MT ENTRY FROM      00011600
*                                               ARRAY                   00011700
         B     LOOPCTL                                                  00011800
SIX      DC    H'6'                                                     00012000
HLDSEMS  DC    H'0'                                                     00012100
         END                                                            00012200
/*




01  ASSGND-DAYS.                                            
    05  FILLER OCCURS 050 TIMES     PIC   X(2).              
                                                             
01  MEETING-TABLE           SYNCHRONIZED.                    
    05  MT-TABLE-ENTRY OCCURS 1000 TIMES INDEXED BY MT-X1.  
        10  MT-SEM-DAYS                 PIC   X(2).          
        10  MT-PERIODS.                                      
            15  MT-PER-FR               PIC  S9(4)  COMP-4.  
            15  MT-PER-TO               PIC  S9(4)  COMP-4.  
                                                             
01  LOOP-CONTROL-DATA.                                      
    05  FIRST-SEM-BIT       PIC  S9(4)  COMP-4  VALUE +0.    
    05  LAST-SEM-BIT-X.                                      
        10  LAST-SEM-BIT    PIC  S9(4)  COMP-4  VALUE +0.    
    05  PERIOD-DISPLACEMENT PIC  S9(4)  COMP-4  VALUE +0.    
           

01  CLASS-RECORD.                                            
    05  CLS-VAR-DATA.                                        
        10  CLS-WORK-PTR.                                    
            15  CLS-MS-PTR          PIC  S9(04) COMP-4.  
        10  CLS-SEM-MODS-X          PIC   X(2).          
      10  CLS-SORT-FLDS.                                  
        15  CLS-SECT-STATUS         PIC   X(1).          
        15  CLS-RSTRCT-STATUS       PIC   X(1).          
        15  CLS-SEATS.                                    
            20  CLS-REM-SEATS-X.                          
                25  CLS-REM-SEATS   PIC  S9(4)  COMP-4.  
            20  CLS-SEX-SEATS-X.                          
                25  CLS-SEX-SEATS   PIC  S9(4)  COMP-4.  
            20  CLS-MNR-SEATS-X.                          
                25  CLS-MNR-SEATS   PIC  S9(4)  COMP-4.  
    05  CLS-MTTAB-PTR-X.                                  
        10  CLS-MTTAB-PTR           PIC  S9(4)  COMP-4.  
    05  CLS-SLOTS-X.                                      
        10  CLS-SLOTS               PIC  S9(4)  COMP-4.  

 
ramkumar1992sp
 
Posts: 71
Joined: Sat Jul 23, 2016 8:52 am
Has thanked: 40 times
Been thanked: 0 time

Re: Help with LH and AR instructions

Postby steve-myers » Thu Dec 08, 2016 10:35 pm

And what is the Cobol CALL statement?
steve-myers
Global moderator
 
Posts: 2105
Joined: Thu Jun 03, 2010 6:21 pm
Has thanked: 4 times
Been thanked: 243 times

Re: Help with LH and AR instructions

Postby ramkumar1992sp » Thu Dec 08, 2016 10:49 pm

There is a call to a different ASM program where in we pass the parameter list and thats copied to XXXXXLST.

001588 955136 2025-SAVE-TABLE-INDEX.                                      
001589 956032     SET LAST-MSTAB-ENTRY TO MS-X1.                          
001590 956928     CALL 'XXXXXARG' USING XXXXX-DAYS XXXXX-TABLE        
001591 957824         LOOP-CONTROL-DATA XXXXX-RECORD BIN-1 BIN-1 BIN-1    
001592 958720         BIN-1 BIN-1.                                        
001593 958800     SET X2F WKF-X1F REQ-XF TO FIRST-XXXXX.              
001594 958820     SET X2L REQ-XL TO LAST-XXXXX.                        
001595 959616     GO TO 0100-START-SCHEDULING-PASS.  
 

Mr Robert Sample and you had helped me understand that program before.

assembler/topic11242.html


Then later we call the above ASM program where in it looks like we read the above parmlist.


     CALL 'XXXQ71S1'.                    
 


I had left out BIN-1 BIN-1 BIN-1 BIN-1 BIN-1 from the parm list in my initial post.
ramkumar1992sp
 
Posts: 71
Joined: Sat Jul 23, 2016 8:52 am
Has thanked: 40 times
Been thanked: 0 time

Re: Help with LH and AR instructions

Postby steve-myers » Thu Dec 08, 2016 10:51 pm

ramkumar1992sp wrote:...
I have the below code in my Assembler program.


GETSEM   LH    R5,2(R2)                   LOAD START PER OF MT ENTRY    
              AR    R5,R1                            ADD ARRAY ADDR    
 


LH will load the contents(half word) of R2 from a displacement of 2. ...
The usual way the LH instruction is expressed in words is something like "Load register 5 with the contents of storage at the address in register 2 plus 2."

For what it's worth, in some computers - though I don't think any are around any more, LH R5,2(0,R2) will be a tiny bit faster than your LH R5,2(R2,0).
steve-myers
Global moderator
 
Posts: 2105
Joined: Thu Jun 03, 2010 6:21 pm
Has thanked: 4 times
Been thanked: 243 times

Re: Help with LH and AR instructions

Postby ramkumar1992sp » Thu Dec 08, 2016 10:58 pm

The address of R2 will be point to MT-SEM-DAYS and then plus 2 will point to address of MT-PER-FR .So that LH will be loading register 5 with the contents of MT-PER-FR..correct?
ramkumar1992sp
 
Posts: 71
Joined: Sat Jul 23, 2016 8:52 am
Has thanked: 40 times
Been thanked: 0 time


Return to Assembler

 


  • Related topics
    Replies
    Views
    Last post