Sunday, November 20, 2011

macro language in system programming


IBM Macro Language

  • Extension of basic assembler language.

  • Means of generating (at assembly time) a commonly used set of instructions as many times as needed.

  • The necessary statements are included in the macro. So when the macro is called (coded), it will produce the necessary statement / statements. It can be called any number of times for generating the code. For example, a macro for generating standard linkage can be written and later it can be called in all the routines, thus saving a lot of typing.

  • Code only the macro name when the statements are to be generated.

  • Also it must be clear that macros do NOT save any space, they just save typing and thus typing errors.

  • Macros are processed prior to assembly, so a macro loop is different than a loop in assembler code.

  • A macro is a separate entities from the programmers code. All macros should be coded in the beginning before the first CSECT.

  • When the macro is invoked, the instructions are generated as if you had typed them in the routine itself.

  • All the macro generated code has a '+' in the first column.
Advantages:Simplify the coding of programs
Reduce number of coding errors

The Difference Between MACROs and Subroutines

Subroutines:Branch out of main logic into a separate logic.
Performed identically each time it is executed.
Subroutines are invoked during execution time.
Macros:Generates assembler code instructions where it is coded.
Depending on how it is coded, different or identical instructions may be generated.
Macros are invoked during assembly time.

Macro Definition

All code in a macro lies between MACRO and MEND statements.
              MACRO
              MACNAME    <---  Prototype statement  (macro name and
                               parameter declarations) is used to 
                               invoke the macro.
              ....
              ....
              MEND
Source macro definition:Macros which are written along with the program are referred to as Source Macro definition.
Library macro definition:Macros which are already written and saved on a disk file to be used later are referred to as Library Macros.
For example: EQUREGS
All source macro definitions must appear before the first CSECT/DSECT. You may not use EJECT, TITLE, SPACE statements in a macro to space the macro code because the macro code is processed pre-assembly. So if you have any of these statements in a macro then the affect of these statements will be seen when the macro is invoked and not within the macro itself. Remember the macro statements are processed before the program is assembled.

Format of a MACRO Definition

     
   MACRO          - The header statement must be first statement

   ANYNAME        - Prototype statement

   ....           - Body of the Macro
   ....             contains Assembler code and also macro
                    processing statements.

   MEND           - Trailer statement  (provides exit)
                  - It must be the last statement
                  - It may have a sequence symbol in column 1
                  - You cannot have more than one MEND statement
                    within a macro

Prototype Statement

  • The name field is required for defining and invoking a macro.

  • It must be right after the header statement ->(MACRO).
Format:
            label or     symbol      0-many parameters
            blank
             !
             !___  if used must have variable symbol  e.g. &LABEL
Parameters can be positional or key word parameters
                 MACRO                   <-- Header statement     
        &LABEL   EXMPL1     &A,&B,&C     <-- Name field
This is what could be typed inside the program.
        CALL1    EXMPL1     VAL1,VAL2,VAL3
By this invoking statement,
  • &A will be replaced by VAL1
  • &B will be replaced by VAL2
  • &C will be replaced by VAL3
through out the macro expansion.
In the above example position of the parameter is important. When the macro is invoked the first value coded is assigned to the first parameter, second value to second parameter and so on so forth. So you must be very careful while coding the values, a mismatch will give you unexpected results. Otherwise, use KEYWORD parameters. If a combination of positional and keyword parameters are used, all the positional parameters must be coded before coding the keyword parameters.
For example, if the prototype statement is coded as follows:
        &LABEL  EXMPL2   &D,&E,&A=,&B=,&C=20
and it is invoked by a routine as follows:
        CALL2   EXMPL2   VAL3,VAL4,B=VAL1,A=(R5,R7),C=,
D will get VAL3, E will get VAL4, B will get VAL1, A will get (R5,R7) and C will get null value.
In this example position of A, B, and C is not important because parameter name is also coded along with the value. D is the first positional parameter and E is the second positional parameter. So when the values are assigned D will get VAL3 and E will get VAL4.
NOTE: The rules are a little different if you are using a combination of keyword and positional parameters in a prototype statement than when you are using actual High Level Assembler (not ASSIST). Talk to your instructor if you want to know the differences.
If there is nothing after the '=' that means a null value is assigned to that parameter. For positional parameters, a null value is assigned to a parameter by coding nothing for the parameter value in the calling statement.
Continuation:When a macro is invoked during assembly, if the prototype statement exceeds one line then break it at a comma, put some character (usually a 'x') in column 72 and start on next line in column 16.
Body of Macro:Body of macro consists of the following:
  • Assembler instructions which are generated when the macro is expanded.
  • Conditional assembly instructions used for generating different code depending on different requirements. These statements are not generated when macro is expanded.
  • Macro inner instructions
  • macro processing instructions, not generated with macro expansion.
  • MNOTE instruction for generating error/warning messages
  • MEXIT instruction for terminating the macro processing in middle.
Comments
  • .* - not generated when macro expands
  • * - generated with macro expansion

Variable Symbols

Definition:Variable symbols are symbols that can be assigned different values by either the programmer or the assembler.
Naming convention :&<alphabetic><up to 6 letters/digits>
There are three types of variable symbol:
  1. Symbolic parameters (Assigned values by a programmer)

  2. System variable symbols (Assigned values by assembler)The following are the most commonly used system variable symbols:
                
                      &SYSNDX    &SYSDATE   &SYSTIME
                      &SYSLIST   &SYSPARM   &SYSECT
    
    Note: Do not start your variable names with &SYS

  3. Set symbols (Assigned values by conditional assembly instruction)
    • Arithmetic set symbols: SETA

    • Binary set symbols: SETB

    • Character set symbols: SETC

Symbolic Parameters

  • Values assigned by the programmer
  • Keyword & positional
  • When macros are expanded, the SYMBOLIC PARAMETERS are replaced by the values that are assigned to them when the macro is invoked. Look at the following macro and the generated code:
           *********************************************************
           *                                                       *
           *  This macro demonstrates how the symbolic parameters  *
           *  are replaced by the assigned values.                 *
           *                                                       *
           *  In effect this macro generates the necessary code to *
           *  compute the sum of two binary integers stored at the *
           *  specified addresses.                                 *
           *                                                       *
           *********************************************************
                   ...
                   MACRO   
         &LABEL    ADD       &NUM1,&NUM2
         &LABEL    L         5,&NUM1
                   A         5,&NUM2
                   ST        5,&NUM1
                   MEND 
                   ...
         MAIN      CSECT
                   ...
                   ...
                   ...               
         SUMIT     ADD       FLD1,FLD2           <<== Invoke the macro
     +   SUMIT     L         5,FLD1              << Code generated  
     +             A         5,FLD2              << by the
     +             ST        5,FLD1              << macro
                   ...
                   ...
                   ...               
                   ADD       FLD3,FLD4           <<== Invoke the macro
     +             L         5,FLD3              << Code generated  
     +             A         5,FLD4              << by the
     +             ST        5,FLD3              << macro
                   ...
                   ...
                   ...               
                   END       MAIN
    

System Variables

  • Values assigned by assembler
  • Various System Variables are
       
                     &SYSNDX, &SYSLIST, &SYSDATE,
                     &SYSTIME, &SYSPARM, &SYSECT
    
  1. &SYSNDX
    • Concatenates a 4 digit number to a symbol of 4 or less characters.
    • It is used to generate a unique suffix for a symbol each time a macro is called.
    • It also assigns a value of 0001 the first time a macro is invoked, which is incremented by one for each subsequent invocation of that macro.
      ***************************************************************
      *                                                             *
      *  The following three MACRO examples relate to the use of    *
      *  &SYSNDX                                                    *
      *                                                             *
      *  First Example : shows the problem caused by a macro which  *
      *                  generates labels - thus the need of &SYSNDX*
      *                                                             *
      *  Second Example: uses &SYSNDX to resolve the problem caused *
      *                  by the first example                       *
      *                                                             *
      *  Third Example : Same as second example but shows a more    *
      *                  sophisticated way of using &SYSNDX         *
      *                                                             *
      ***************************************************************
    
      ***************************************************************
      *                                                             *
      *  First Example : shows the problem caused by a macro which  *
      *                  generates labels - thus the need of &SYSNDX*
      *                                                             *
      ***************************************************************
                   MACRO
         &LABEL    ADD       &NUM1,&NUM2
         &LABEL    ST        5,SAVE
                   L         5,&NUM1
                   A         5,&NUM2
                   ST        5,&NUM1
                   B         NEXT
         SAVE      DC        F'-1'
         NEXT      DS        0H
                   L         5,SAVE
                   MEND
    
         MAIN      CSECT
                   ...
                   ...
                   ADD       FLD1,FLD2
        +          ST        5,SAVE
        +          L         5,FLD1 
        +          A         5,FLD2 
        +          ST        5,FLD1 
        +          B         NEXT
        +SAVE      DC        F'-1'
        +NEXT      DS        0H
        +          L         5,SAVE
                   ...
                   ...               
                   ADD       FLD1,FLD2
        +          ST        5,SAVE
        +          L         5,FLD1 
        +          A         5,FLD2 
        +          ST        5,FLD1 
        +          B         NEXT
        +SAVE      DC        F'-1'
        +NEXT      DS        0H
        +          L         5,SAVE
                   ...
                   ...               
        FLD1       DC        F'10'  
        FLD2       DC        F'20'
                   ...
                   END       MAIN     
    
    As you can see in the above example, the labels - SAVE and NEXT, were both generated each time the macro was called. This will lead to the problem of DUPLICATE LABELS. We take care of this problem by using &SYSNDX in the next example.
      *************************************************************
      *  Second Example: uses &SYSNDX to resolve the duplication  *
      *                  problem caused by the first example      *  
      *************************************************************
                   MACRO
         &LABEL    ADD       &NUM1,&NUM2
         &LABEL    ST        5,SAVE&SYSNDX
                   L         5,&NUM1
                   A         5,&NUM2
                   ST        5,&NUM1
                   B         NEXT&SYSNDX
         SAVE&SYSNDX    DC   F'-1'
         NEXT&SYSNDX    DS   0H
                        L    5,SAVE&SYSNDX
                   MEND
         MAIN      CSECT
                   ...               
                   ADD       FLD1,FLD2
        +          ST        5,SAVE0001
        +          L         5,FLD1 
        +          A         5,FLD2 
        +          ST        5,FLD1 
        +          B         NEXT0001
        +SAVE0001     DC        F'-1'
        +NEXT0001     DS        0H           
        +          L         5,SAVE0001
                   ...               
                   SUMIT     FLD1,FLD2
        +          ST        5,SAVE0002
        +          L         5,FLD1 
        +          A         5,FLD2 
        +          ST        5,FLD1 
        +          B         NEXT0002
        +SAVE0002     DC        F'-1'
        +NEXT0002     DS        0H           
        +          L         5,SAVE0002
                   ...
        FLD1       DC        F'10'  
        FLD2       DC        F'20'
                   ...
                   END       MAIN     
    
    As seen in this example we have taken care of the duplication problem. Now every time the macro is invoked the labels will be unique. But another minor problem caused now is the misalignment of the expanded code. This is caused by the fact that &SYSNDX is seven characters whereas its replacement is only four characters. This can be solved if we could somehow make &SYSNDX smaller. See the solution for this problem in the next example.Note: Mis-alignment will not cause any assembler or execution errors, it just doesn't look good.
      *************************************************************
      *  Third Example : Same as second example but shows a more  *
      *                  sophisticated way of using &SYSNDX and   *
      *                  solving the alignment problem.           *
      *                                                           *
      *                  A local character variable &NDX is       *   
      *                  declared and assigned a value of         * 
      *                  '&SYSNDX'. Then &NDX can be used instead *
      *                  of &SYSNDX, thus the remedy.             *   
      *************************************************************
                   MACRO
         &LABEL    ADD       &NUM1,&NUM2
                   LCLC      &NDX
         &NDX      SETC      '&SYSNDX'
         &LABEL    ST        5,SAVE&NDX
                   L         5,&NUM1
                   A         5,&NUM2
                   ST        5,&NUM1
                   B         NEXT&NDX
         SAVE&NDX  DC   F'-1'
         NEXT&NDX  DS        0H           
                   L    5,SAVE&NDX
                   MEND
    
         MAIN      CSECT
                   ...
                   ...
                   ADD       FLD1,FLD2
        +          ST        5,SAVE0001
        +          L         5,FLD1 
        +          A         5,FLD2 
        +          ST        5,FLD1 
        +          B         NEXT0001
        +SAVE0001  DC        F'-1'
        +NEXT0001  DS        0H           
        +          L         5,SAVE0001
                   ...               
                   ADD       FLD1,FLD2
        +          ST        5,SAVE0002
        +          L         5,FLD1 
        +          A         5,FLD2 
        +          ST        5,FLD1 
        +          B         NEXT0002
        +SAVE0002  DC        F'-1'
        +NEXT0002  DS        0H           
        +          L         5,SAVE0002
                   ...
        FLD1       DC        F'10'  
        FLD2       DC        F'20'
                   ...               
                   END       MAIN
    

  2. &SYSLIST - Used to refer to any positional parameter in a macro definition, or also can refer to entry in a positional parameter sublist.
    • &SYSLIST(n) to refer to a positional parameter

    • &SYSLIST(n,m) to refer to sublist of positional parameter
      
                      CALL3  EXMPL4   ONE,TWO,(R5,R6,R7,R8),,NINE,(R1)
    
                      code in macro             generated value
                      -------------             ---------------
                      &SYSLIST(2)                  TWO
                      &SYSLIST(3,3)                R7
                      &SYSLIST(4)                  null
                      &SYSLIST(6,1)                R1
    
    If a keyword parm should specify several values. Enclose them in () but don't use &SYSLIST to refer to them. Use the variable name itself.
                                
                      MACRO
                      SUBLISTS   &P1,&KEY=(0,1,3)
             &P1(1)   DC         F'&KEY(1)'
             &SYSLIST(1,2)  EQU  &P1(2)
                      MEND
                    
             MAIN     CSECT        
                      ... 
                      CALL     SUBLISTS   (HERE,THERE),KEY=(5,6,7)
             +HERE    DC     F'5'
             +THERE       EQU    THERE
                      ...
                      ...   
                      END      MAIN
    

  3. &SYSDATE - To obtain date on which source module was assembled MM/DD/YY.

  4. &SYSTIME - To obtain time at which source module was assembled hh.mm.

  5. &SYSECT - To generate the name of the current control section. (CSECT in which macro is called)

  6. &SYSPARM - Lets you pass a character string into a source module from the JCL that invokes the assembler.

SET Symbols

  • The LCLA, LCLB, and LCLC instructions may be used to declare and assign initial values to local SET symbols. Any variable symbols so declared is local to the macro-definition in which it is declared. The same variable symbol may not be used as a formal parameter and as a SET symbol in the same macro-definition.

  • The GBLA, GBLB, and GBLC instructions serve to declare and assign initial values to global SET symbols. All local and global SET symbols must be declared in each and every macro-definition that uses the SET symbol. Whereas a local SET symbol is initialized each time the macro is used. Thereafter, the global SET symbol is said to be global through the entire assembly.

  • Used to define and assign values while the macro is processing.

  • There are three types of SET Symbol:
    1. Arithmetic
    2. Binary
    3. Character

  • These variables can be declared as:
    • Global: Initialized the first time and then values are saved from one call to another.
    • Local : Reinitialized for each call.

  • All the Set Symbols must be declared right after the prototype statement. Also, all Global symbols must be declared before Local Symbols.

  • GBLA, GBLB, GBLC are used for declaring global variables and

  • LCLA, LCLB, LCLC are used for declaring local variables.
  1. Arithmetic:
    • 32 bit field
    • value can range from -2**31 to 2**31 - 1
                   GBLA   symbol1,symbol2....  set to zero first time 
                                               then maintain old value
                                               from the last invocation 
                                               of the macro 
                   e.g.  GBLA     &CNT1,&CNT2
    
    
                   LCLA   symbol1,symbol2...   set to zero every time 
                                               macro is invoked
    
                   e.g.  LCLA     &CNT1,&CNT2
                   
                   SETA command is used to alter value of an arithmetic
                        set symbol
    
                      symbol  SETA   arithmetic expression
    
                  for example,
     
                    &CNTR     SETA   1            init &CNTR to 1
                    &CNTR     SETA   &CNTR+1      add 1 to &CNTR
                    &CNTR     SETA   &CNTR*5      multiply &CNTR by 5
    
    
      **************************************************************
      *  The following two MACRO examples illustrate the use of    *
      *  Local and Global arithmetic variables.                    *
      *                                                            *
      *  In effect both the macros generate the 16 register equate *
      *  statements.                                               *
      *                                                            *
      *  First Example : uses a Local arithmetic variable          *
      *                                                            *
      *  Second Example: same as first example but instead of local*
      *                  variable a global variable is used        *
      *                                                            *
      *  NOTE: These two examples also use conditional assembly &  *
      *        concatenation which are discussed in detail later.  *  
      ************************************************************** 
      **************************************************************
      *  First Example : uses a Local arithmetic variable          *  
      ************************************************************** 
                  MACRO
        &LABEL    EQUREGS
                  LCLA    ®
        .LOOP     AIF     (® GT 15).ENDLOOP
        R®     EQU     ®
        ®      SETA    ®+1
                  AGO     .LOOP
        .ENDLOOP  ANOP
                  MEND
                  ...
         MAIN     CSECT
                  EQUREGS
         +R0      EQU     0
         +R1      EQU     1
         +R2      EQU     2
         +R3      EQU     3
                ......
         +R14     EQU     14
         +R15     EQU     15
                ......
                  EQUREGS
         +R0      EQU     0
         +R1      EQU     1
         +R2      EQU     2
         +R3      EQU     3
                ......
         +R14     EQU     14
         +R15     EQU     15
                  END     MAIN
    
    As you can see above, EQUREGS was called twice and the statements were generated both the times. This problem can be solved by using a global variable as shown in the next example.
      ****************************************************************
      *                                                              *
      *  Second Example : uses a Global arithmetic variable and thus *
      *                   solves the problem of unnecessary expansion*
      *                                                              * 
      *  Note: This is not the only application of Global Variables  *
      *                                                              *
      ****************************************************************
                  ...
                  MACRO
        &LABEL    EQUREGS
                  GBLA    ®
        .LOOP     AIF     (® GT 15).ENDLOOP
        R®     EQU     ®
        ®      SETA    ®+1
                  AGO     .LOOP
        .ENDLOOP  ANOP
                  MEND
                  ...
         MAIN     CSECT
                  EQUREGS
         +R0      EQU     0
         +R1      EQU     1
         +R2      EQU     2
         +R3      EQU     3
                ......
                ......
         +R14     EQU     14
         +R15     EQU     15
                ......
                ......
                  EQUREGS                <<<=== this invocation does 
                  END     MAIN                  not generate anything
    
    As you can see, nothing was generated when the macro was invoked the second time, since after the first invocation value of &REG was 16 and was never reinitialized to 0.

  2. Binary:
    • One bit field, can only have two values - 0 or 1
    • generally used as flag
      
                   GBLB   &BIN1   <---  set to zero first time then
                                        maintain old value
    
                   LCLB   &BIN1   <---  set to zero everytime macro
                                        is invoked
    
                   SETB command is used to alter the value of a 
                        binary set symbol
    
                   symbol  SETB   logical expression
                   &BIN1   SETB   1
                   &BIN2   SETB   (&SYM LT 7)       if true &BIN2=1
                   &BIN3   SETB   ('&SYM1' EQ 'NO') if true &BIN3=1
    
      ***************************************************************
      *  The following MACRO example is the same as the one used for*
      *  illustrating the use of Arithmetic variables.              *
      *                                                             *
      *  Here instead of using a Global arithmetic variable we are  *
      *  using a global binary variable as a flag to keep track of  *
      *  whether the macro has already been invoked.                *
      ***************************************************************
                  MACRO
        &LABEL    EQUREGS
                  GBLB    &FLAG
                  LCLA    ®
                  AIF     (&FLAG).NOTAGAN
        &FLAG     SETB    1      
        .LOOP     AIF     (® GT 15).ENDLOOP
        R®     EQU     ®
        ®      SETA    ®+1
                  AGO     .LOOP
        .ENDLOOP  ANOP
        .NOTAGAN  ANOP
                  MEND
    
         MAIN     CSECT
                  EQUREGS
         +R0      EQU     0
         +R1      EQU     1
         +R2      EQU     2
         +R3      EQU     3
                ......
         +R14     EQU     14
         +R15     EQU     15
                ......
                  EQUREGS                <<<=== this invocation does 
                  END     MAIN                  not generate anything 
    

  3. Character:
    • used for character strings needed during macro processing
    • the string length can be 0 to 255 characters (if length exceeds 255, truncation occurs on the the right hand side)
    • Character strings can be created by:
      1. a string constant - 'AB'
      2. a combination of character set symbol and a string constant - '&CHR1.ABC'
      3. a combination of two character set symbols - '&CHR1&CHR2'
                   
                   GBLC   &CHR1,&CHR2   - set to null string first time
                                          and never reinitialized
    
                   LCLC   &CHR1,&CHR2   - set to null string everytime
                                          macro is invoked
    
                   SETC  command is used to alter the contents of  
                         a character set symbol.
    
                   symbol  SETC   character string
    
    
    
                   MACRO
        &LABEL     MOVEIT ®,&RECFLD,&SENFD
                   LCLC  &NDX
        &NDX       SETC  '&SYSNDX'
                   EX    ®,MOVE&NDX
                   B     ARND&NDX
        MOVE&NDX   MVC   0(0,&RECFLD),0(&SENFD)                 
        ARND&NDX   DS    0H
                   MEND 
    
    We have already seen an example of using character set symbols: -- third example for &SYSNDX, will see some more later on.

Concatenation Rules

When character strings are to be concatenated special consideration has to be made when the concatenated string is not a set symbol but a string constant.
There must be something to indicate the end of the variable and start of the string.
Let us take a look at the following two examples of concatenation (In both the examples a string 'ABCD' is concatenated to a set symbol):
               1.  'ABCD&CHR1'   or       2. '&CHR1ABCD'<-- WRONG
In the second type how will the macro processor know that the name of variable is &CHR1 and not &CHR1ABCD, i.e. we must have some kind of delimiter to indicate the end of set symbol. In the first type '&' acted as as a delimiter for the second one '.' must be used as a delimiter, so the proper way to code the second type would be
            '&CHR1.ABCD'. <-- CORRECT


  **************************************************************** 
  *                                                              *
  *  The following example just shows how  the concatenation     *
  *  will work under various circumstances.                      *
  *                                                              *
  *  It also illustrates the use of character set symbols.       *
  *                                                              *
  *  In effect this macro will just generate some DC statements. *
  *                                                              *
  *  Note: Don't look at what the generated assembler code does  *
  *        just see what is being generated.                     *
  *                                                              *
  ****************************************************************

              MACRO
    &LABEL    GENDCS
              LCLC    &CHR1,&CHR2,&CHR3,&CHR4,&CHR5
    &CHR1     SETC    'ABCD'            
    &CHR2     SETC    '1234' 
    &CHR3     SETC    '&CHR1.XYZ'          
    &CHR4     SETC    'XYZ&CHR2&CHR1'
    &CHR5     SETC    '&CHR1.&CHR2..EFGH'
              DC      C'&CHR1'
              DC      C'&CHR2'
              DC      C'&CHR3'
              DC      C'&CHR4'
              DC      C'&CHR5'
              MEND


     MAIN     CSECT
              ....
              ....
              GENDCS 
              DC      C'ABCD'
              DC      C'1234'
              DC      C'ABCDXYZ'
              DC      C'XYZ1234ABCD'
              DC      C'ABCD.1234.EFGH'
              ....
              ....
              END     MAIN

MNOTE and MEXIT

Frequently, it is necessary to generate messages during macro processing. Some times messages are just informative and at other times they could be error messages and must be considered as assembly time errors.
MNOTE can be used to generate messages along with an optional severity code.
  • severity code determines whether the generated message is an error or just informative.

  • message with severity code of 4 or higher is considered to be an error message.
              MNOTE   4,'message'   ==>  4,message

              MNOTE   'message'     ==>  message

              MNOTE   12,'message'  ==>  message
MEXIT:
  • provides exit point from inside the macro body.
  • MEXIT must be used whenever macro processing has to be stopped in the middle.
All the following examples will incorporate the use MNOTE & MEXIT.

Conditional Assembly

  • Provides a way to alter the sequence in which source program statements are processed by the assembler.

  • Can branch within the macro to generate different code depending on different requirements and requests.

  • Conditional assembly statements are not generated when macro expands.

  • Labels used in conditional assembly instructions are referred to as Sequence Symbols.

Sequence Symbols

  • Naming convention of Sequence Symbol :
    .<alphabet><0-6 digits/letters>
    
  • Sequence Symbols are used in operand field of conditional assembly branch instruction.

  • You cannot put a sequence symbol on any assembler instruction which may be generated.
Various conditional assembly instructions are:
sequence symbol    AIF    sequence symbol

sequence symbol    AGO   sequence symbol

sequence symbol    ANOP   <== just like DS  0H  in assembler



           MACRO
           EQURGS
           GBLA   &CNTR
  .LOOP    AIF    (&CNTR  EQ 15).ENDLOOP
  R&CNTR   EQU    &CNTR          
  &CNTR    SETA   &CNTR+1
           AGO   .LOOP
 .ENDLOOP  ANOP
           MEND
Note: .LOOP and .ENDLOOP are sequence symbols.
  **************************************************************** 
  *                                                              *
  *  The following example illustrates the use of conditional    *
  *  assembly instructions and it also illustrates the use       *
  *  of MNOTE and MEXIT commands.                                *
  *                                                              *
  *  Note: The CSECT which invokes this macro is on the next     *
  *        page but the macro expansion is not shown and is      *
  *        left as an exercise for you. Do it to get a better    *
  *        feel of the macros.                                   *
  *                                                              *
  ****************************************************************


              MACRO
    &LABEL    EXITLINK  &TYPE
              AIF     ('&TYPE'  NE '').FOUND
              MNOTE   '**** MISSING TYPE PARAMETER'
              MEXIT
    .FOUND    ANOP  
              AIF     ('&TYPE'  EQ 'N').NORMAL 
              AIF     ('&TYPE'  EQ 'R').RETURN
              AIF     ('&TYPE'  EQ 'V').VALUE  
              AIF     ('&TYPE'  EQ 'B').BOTH   
              MNOTE   '****INVALID VALUE FOR TYPE ****'
              MEXIT
     .NORMAL  ANOP
              L       13,4(13)             PICK BACKWARD POINTER
              LM      14,12,12(13)         PICK ALL REGS 
              BR      14                   RETURN TO CALLER
              AGO     .DONE
     .RETURN  ANOP
              L       13,4(13)             PICK BACKWARD POINTER
              L       14,12(13)            PICK ALL REGS EXCEPT
              LM      0,12,20(13)             REGISTER 15 
              BR      14                   RETURN TO CALLER
              AGO     .DONE
     .VALUE   ANOP
              L       13,4(13)             PICK BACKWARD POINTER
              LM      14,15,12(13)         PICK ALL REGS EXCEPT
              LM      1,12,24(13)             REGISTER 0 
              BR      14                   RETURN TO CALLER
              AGO     .DONE
     .BOTH    ANOP
              L       13,4(13)             PICK BACKWARD POINTER
              L       14,12(13)            PICK ALL REGS EXCEPT
              LM      1,12,24(13)             REGISTER 15 AND 0
              BR      14                   RETURN TO CALLER
     .DONE    ANOP
              MEND
     *
     MAIN     CSECT
              ....
              ....
              EXITLINK Q





                                           try to fill these
              EXITLINK                     blank areas






              EXITLINK V    








              EXITLINK N          








              EXITLINK R              








              EXITLINK B                  





              END     MAIN

Data Attributes

  • For each constant or instruction the assembler assigns attributes.

  • By specifying attributes in conditional assembly instructions the conditional assembly logic can be controlled. (It can control sequence and contents of the statements generated)

T' - Type attribute

  • Indicates the type of data of the field assigned to the symbolic parameter when the macro is invoked.

  • If &PARM is a symbolic parameter on a prototype statement and T'&PARM is coded in the macro, following table summarizes all the possible values that can be assigned to T'&PARM.
  Symbols for DC or DS statements      Meaning                    
             A                         Address constants
             B                         Binary constants
             C                         Character constants

             F                         Full word fixed point const. 
             H                         Half word fixed point const.
             P                         Packed decimal constant
             R                         A-constant or V-constant
             X                         Hexadecimal constant
             Z                         Zoned decimal constant
             V                         V-constant

  Symbols that name other DC, DS statements      Meaning          
       
             I                                   Machine instr.   
             J                                   CSECT name
             M                                   Macro instr.
             T                                   EXTRN symbol     
             W                                   CCW instr.       
   
  Symbols used for macro operand only           Meaning           
             N                                   Self-defining term
             O                                   Omitted operand  
             U                                   Undefined


  ****************************************************************
  *                                                              *
  *  The following example illustrates the use of TYPE           *
  *  attribute.                                                  *
  *                                                              *
  ****************************************************************


                     MACRO
                     CHECKT  &PARM1,&PARM2
                     LCLC    &CHR1,&CHR2  
                     AIF  (T'&PARM1 NE  'O').FOUND
                     MNOTE '**** MISSING PARAMETER ****'
                     MEXIT
             .FOUND  ANOP  
              &CHR1  SETC  T'&PARM2
              &CHR2  SETC  T'&PARM1
              &CHR2  SETC  '&CHR2&CHR1'
                     DC    C'&CHR2'
                     MEND


     MAIN     CSECT
              ....
              ....
              CHECKT  TABLE,PLINE
     +        DC      C'FC' 
              ....
              ....
     TABLE    DS      20F   
     PLINE    DC      CL12
              ....
              ....
              END     MAIN

L' - Length attribute of symbolic parameters

  • a numeric value equal to the number of bytes occupied by the data that is represented in the expression.

  • the value of the symbolic parameter used with this attribute must be a label in the calling program.

  • this cannot be used for checking a missing parameter.

  • this does not give the total storage occupied, it just gives the length attribute value - check third invocation of the macro given below
  ****************************************************************
  *                                                              *
  *  The following example illustrates the use of LENGTH         *
  *  attribute.                                                  *
  *                                                              *
  ****************************************************************
                 MACRO
        &LABEL   MOVEIT   &ABC,&XYZ
                 MVC      &ABC.(L'&XYZ),&XYZ
                 MEND

        MAIN     CSECT 
                 ....
                 ....   
                 MOVEIT   PLINE,TABLE
        +        MVC      PLINE(80),TABLE
                 ....
                 .... 
                 MOVEIT   PLINE,80
        +        MVC      PLINE(0),80    
                 ....
                 ....
                 MOVEIT   PLINE,TABLE1
        +        MVC      PLINE(20),TABLE1
                 ....
        PLINE    DS       CL133
        TABLE    DS       CL80
        TABLE1   DS       4CL20
                 END      MAIN
In the first invocation the length attribute for TABLE is 80.
In the second invocation length will be 0 because 80 is not a variable defined in the calling program. You will also get a message from the assembler.
In the third invocation length attribute is 20, 4 is the multiplication factor and thus is not accounted as a part of the length attribute.

K' - Count attribute

  • Numeric value equal to the numbers of characters in the actual parameter being passed.

  • If K'&PARM is zero, it means that the parameter is missing (no value assigned)
       
  ****************************************************************
  *                                                              *
  *  The following example illustrates the use of COUNT          *
  *  attribute.                                                  *
  *                                                              *
  ****************************************************************


                 MACRO
        &LABEL   CHECKK   &PARM1,&PARM2
                 LCLA     &CNTR1,&CNTR2
                 AIF      (K'&PARM1 NE 0).FOUND
                 MNOTE    '***MISSING PARAMETER***'
                 MEXIT
        .FOUND   ANOP 
        &CNTR1   SETA     K'&PARM1
        &CNTR2   SETA     K'&PARM2-2
                 XPRNT    =C&PARM2,&CNTR2
                 LA       5,&CNTR1          
                 MEND



        MAIN     CSECT 
                 ....
                 ....   
                 CHECKK   JUNKY,'1  TOP OF PAGE'
        +        XPRNT    =C'1  TOP OF PAGE',14
        +        LA       5,5  
                 ....
                 .... 
                 CHECKK   WHATEVER,'0  DOUBLE SPACE'
        +        XPRNT    =C'0  DOUBLE SPACE',15
        +        LA       5,8  
                 ....
                 ....
                 END      MAIN

N' - Number attribute

  • Number of operand in an operand sublist

  • Use only in arithmetic expressions

  • N'&SYSLIST will give you number of positional parameters on the prototype statement in a macro call

  • N'&SYSLIST(m) - refers to number of sublist entries in the mth operand.

  • N'&PARM - number of sublist entries in the mentioned operand
  ****************************************************************
  *  The following example illustrates the use of NUMBER         *
  *  attribute.                                                  *
  ****************************************************************
                 MACRO
        &LABEL   CHECKN   &PARM1,&PARM2,&PARM3
                 LCLA     &CNTR1,&CNTR2
                 LCLC     &CHR 
        &CNTR1   SETA     N'&SYSLIST
        &CNTR2   SETA     1
        .LOOP    AIF      (&CNTR2 GT  &CNTR1).DONE
        .*
        .*     THE FOLLOWING SETC COMMAND IS TO PICK UP
        .*     THE PARAMETERS FROM THE PROTOTYPE STATEMENT
        .*
        &CHR     SETC     &SYSLIST(&CNTR2)
                 DC       A(&CHR)
        &CNTR2   SETA     &CNTR2+1
                 AGO      .LOOP                       
        .DONE    ANOP  
                 MEND

        MAIN     CSECT 
                 ....   
                 CHECKN   TABLE,EOT,CARD
        +        DC       A(TABLE)
        +        DC       A(EOT)             
        +        DC       A(CARD)
                 ....
                 CHECKN   CARD,OPTBYTE
        +        DC       A(CARD)                    
        +        DC       A(OPTBYTE)
                 ....
        TABLE    DS       20F
        CARD     DS       CL80
        OPTBYTE  DS       X
        EOT      DS       F
                 END      MAIN
Similar logic can be extended to sub lists also. Try it yourself.
  ****************************************************************
  *  The following example illustrates the use of generating a   *
  *  label and macro documentation.                              *
  *                                                              *
  *  Checking for missing parameter is not done here and in most *
  *  of other the examples, but it is good practice to           * 
  *  incorporate missing parameter check in every macro which    * 
  *  uses symbolic parameters.                                   *
  ****************************************************************
                 MACRO
        &LABEL   CHECLBL  &PARM1,&PARM2
        .*       THIS MACRO GENERATES THE NECESSARY CODE TO ADD
        .*       TWO NUMBERS
        .*
                 LCLC    &NDX
        &NDX     SETC    '&SYSNDX'           
        *        SAVE THE REGISTER BEING CHANGED
                 ST      2,RGSV&NDX
        *
                 L       2,&PARM1        GET THE CONTENTS OF FIELD1
                 A       2,&PARM2        ADD CONTENTS OF FIELD2
                 ST      2,&PARM1        PUT RESULT IN FIELD1
        *
        *        RESTORE THE REGISTER BEING CHANGED         
                 L       2,RGSV&NDX                       
        *                                                 
                 B       ARND&NDX
        RGSV&NDX DS      F
        ARND&NDX DS      0H
                 MEND 

        MAIN      CSECT 
                  ....
                  B      SUMIT          <<<===== Refer to
                  ....                           note on next page.
        SUMIT     CHECLBL  FIELD1,FIELD2
        +*        SAVE THE REGISTER BEING CHANGED
        +         ST     2,RGSV0001
        +*
        +         L      2,FIELD1           
        +         A      2,FIELD2
        +         ST     2,FIELD1
        +*        RESTORE THE REGISTER BEING CHANGED         
        +         L      2,RGSV0001
        +*
        +         B      ARND0001
        +RGSV0001 DS     F    
        +ARND0001 DS     0H              
                 ....
        FIELD1   DC       F'10'
        FIELD2   DC       F'20'
                 END      MAIN
In the previous example the generated documentation is very obvious and as you can see the macro documentation (.*) was not generated. Everything seems ok here but there is a problem which might have made you pull your hair if you didn't know about it.
The marked instruction (B SUMIT) will give you an undefined symbol error. This is because once the macro expands the macro statement itself is nothing but a line of documentation. So the label SUMIT doesn't actually exist, thus the undefined symbol error. This problem is solved by making sure that the macro generates a label if the invoking statement has a label on it. See the corrected example below:
                 MACRO
        &LABEL   CHECLBL  &PARM1,&PARM2
        .*
        .*       THIS MACRO GENERATES THE NECESSARY CODE TO ADD
        .*       TWO NUMBERS
        .*
                 LCLC    &NDX
        &NDX     SETC    '&SYSNDX'          
        .*
        .*       ALL THE NECESSARY CHECKS HAVE BEEN DONE AT
        .*       THIS POINT. SO NOW WE CAN GENERATE THE LABEL,    
        .*       IF THERE IS NO LABEL ON THE INVOKING STATEMENT,  
        .*       ONLY DS 0H WILL BE GENERATED
        .*
        &LABEL   DS      0H
        *        SAVE THE REGISTER BEING CHANGED
                 ST      2,RGSV&NDX
        *
                 L       2,&PARM1        GET THE CONTENTS OF FIELD1
                 A       2,&PARM2        ADD CONTENTS OF FIELD2
                 ST      2,&PARM1        PUT RESULT IN FIELD1
        *
        *        RESTORE THE REGISTER BEING CHANGED         
                 L       2,RGSV&NDX                       
        *                                                 
                 B       ARND&NDX
        RGSV&NDX DS      F
        ARND&NDX DS      0H
                 MEND 
NOTE: Expansion of the macro is left for you to figure out.

Additional Macro Example

******************************************************************
*                                                                *
*      This macro tests whether &SUM contains a label            *
*      representing an address or a register in parenthesis.     *
*      &SUM is the place where the result of the addition        *
*      will be stored.                                           *
*                                                                *
******************************************************************


          MACRO
&LABEL    SORT      &TABLE,&SIZE
          LCLC      &INREG
          LCLC      &NDX
&NDX      SETC      '&SYSNDX'
          AIF       ('&TABLE' NE '').CHKSIZE
          MNOTE     12,'*** TABLE OPERAND IS MISSING ***'
          MEXIT
.CHKSIZE  ANOP
          AIF       (K'&SIZE NE 0).CKLABEL
          MNOTE     12,'*** SIZE OPERAND IS MISSING ***'
          MEXIT
.CKLABEL  ANOP
          AIF       (T'&LABEL EQ '0').NOLABEL
&LABEL    DS        0H  
.NOLABEL  ANOP
          ST        1,RGSV&NDX
          STM       14,15,RGSV&NDX
&INREG    SETC      'NO'
          AIF       ('&TABLE'(1,1) NE '(').NOTREG
          ST        &TABLE(1),PLST&NDX
&INREG    SETC      'YES'
.NOTREG   ANOP
          CNOP      0,4
          BAL       1,CALL&NDX
          AIF       ('&INREG' EQ 'NO').ACON
PLST&NDX  DC        A(0)
          AGO       .PARMSIZ
.ACON     ANOP
          DC        A(&TABLE)
.PARMSIZ  ANOP  
          DC        A(&SIZE)
RGSV&NDX  DS        3A
CALL&NDX  EQU       *
          L         15,=V(MYSORT)
          BALR      14,15
          L         1,RGSV&NDX
          LM        14,15,RGSV&NDX+4
          MEND

     
 MACTEST   CSECT
           standard linkage goes here!!    
 *
 FIRST     SORT  TABLE,TBLSIZE
+FIRST     DS    0H
+          ST    1,RGSV0011
+          STM   14,15,RGSV0011+4
+          CNOP  0,4
+          BAL   1,CALL0011
+          DC    A(TABLE)
+          DC    A(TBLSIZE)
+RGSV0011  DS    3A    
+CALL0011  EQU   *
+          L     15,=V(MYSORT)
+          BALR  14,15
+          L     1,RGSV0011
+          LM    14,15,RGSV0011+4
 *
           LA    R5,TABLE
           SORT  (R5),TBLSIZE
+          ST    1,RGSV0012
+          STM   14,15,RGSV0012+4
+          ST    R5,PLST0012
+          CNOP  0,4
+          BAL   1,CALL0012
+PLST0012  DC    A(0)
+          DC    A(TBLSIZE)
+RGSV0012  DS    3A
+CALL0012  EQU   *
+          L     15,=V(MYSORT)
+          BALR  14,15
+          L     1,RGSV0012
+          LM    14,15,RGSV0012+4
 *
           SORT  TABLE
+  12,*** SIZE OPERAND IS MISSING *** 
 *
           SORT  ,TBLSIZE
+  12,*** TABLE OPERAND IS MISSING *** 
           exit linkage goes here!!
 * 
 TABLE     DC   F'24,32,2,7,91,83,39,67'  
 TBLSIZE   DC   F'8'
           LTORG
                =V(MYSORT)
           DROP

 MYSORT    CSECT
           BR  R14
           END MACTEST      


0 comments: