Calling C from Rexx – overview

Rexx is a very flexible language. You can call other Rexx programs, you can call z/OS functions, or you can call functions written in C or assembler.

Programming a C function was not straight forward because it involved twisting and bending to get it to work – one of the downsides of being flexible.

See

What options are there?

You can use

  • call function(p1,p2,p3) This gets passed an array of parameters, and has to return data in and an EVALBLOCK. See here.
  • address link program “p1 p2 p3” where “p1 p2 p3” is a literal string which is passed to your program
  • address linkmvs program “p1 p2 p3” where p1, p2, p3 are variable names, whose values are substituted before being passed to the program. If the parameter is not a variable – the parameter is passed through as is. The program gets passed a list
    • length p1 value, p1 value
    • length p2 value, p2 value
    • length p3 value, p3 value
  • address linkpgm program “p1 p2 p3” where p1, p2, p3 is a variable names, whose values are substituted before being passed to the program. If the parameter is not a variable – the parameter is passed through as is. The program gets passed a list of (null terminated values)
  • p1 value
  • p2 value
  • p3 value

If you have code

a = "COLIN A"
address linkpgm CPQUERY "A B C"

The parameters received by the program are

  • “COLIN A”
  • “B”
  • “C”

If you pass a string with hex value in it – it may have a 0x00 – which would look like an end of string. This means the linkpgm is not a good interface for passing non character data.

Passing back values

With address link you can pass back a return code. You can also use Rexx services to get and set variables in the calling rexx programs.

With address linkmvs and address linkpgm you can update the values passed in (this is non trivial). You can set a return code and use Rexx services to get and set variables in the calling rexx programs.

Which should I use?

address link

The simplest, where you have greatest control is address link. Your program gets passed a string which it can process.

address linkmvs and address linkpgm

These are similar, and you need to be careful.

A = "COLINA" 
B = ""
P = "A B C"
(1) address linkmvs CPLINKM "A B C "
(2) address linkmvs CPLINKM "P"
(3) address linkmvs CPLINKM P

With the above, my program produces.

(1)
parm 0 >COLINA<
parm 1 is Null
parm 2 >C<

(2)
parm 0 >A B C<

(3)
parm 0 >COLINA<
parm 1 is Null
parm 2 >C<

If you are using linkpgm or linkmvs, the parameter specified will be substituted (if there is a variable with the same name).

my_stem. = "used for variables"
address linkmvs CPMVS "my_stem. "

If you want to specify a stem to your program so you can set my_stem.0, my_stem.1 etc you will not be using the value you specify, it will be used for variables.0 etc.

Using

address linkmvs CPLINKM "A 'B' C "

gives return code -2.

The return code set in RC may be -2, which indicates that processing of the variables was not successful. Variable processing may have been unsuccessful because the host command environment could not: Perform variable substitution before linking to or attaching the program.

Calling C from Rexx – writing the program.

You can write a Rexx external function in C, have it process the parameters, and return data.

I found writing a program to do this was non trivial, and used bits of C I was not familiar with.

See Calling C from Rexx – accessing variables.

If you use the address… environment, the C program does not pass parameters using the normal “main” interface;

int main( int argc, char **argv ){}

because the parameters are passed in via register 1, and you need a different technique.

Header files

There are header files in SYS1.SIEAHDR.H for the Rexx facilities.

#include <irxefpl.h> // REXX External Functions Parameter List 
#include <irxargtb.h> // REXX Argument Table control block mapping
#include <irxshvb.h> // REXX Shared Variable Request Block
#include <irxenvb.h> // REXX Environment Block
#include <irxexte.h> // REXX access to shared variables etc

Program for address link …

With this, the parameters are passed in one string. The program is given the address and the length of the string.

#pragma runopts(plist(os)) 
struct plistlink {
char ** pData;
int * len;
};
int main() {
struct plistlink * pLink = (struct plistlink *)__R1;
int k = * pLink -> len;
char * pc = *pLink -> pData;
printf("plistlink length %i %.*s\n",k,k,pc);
return 0;
}

The important things to note here are

  • #pragma runopts(plist(os)) this says that the parameters are in standard z/OS parameter format based off register 1.
  • int main() this defines the entry point, and sets up the C environment.
  • __R1 is a special #define which returns the value of register one on entry to the routine.
  • struct plistlink * pLink = (struct plistlink *)__R1; defines the input parameter list.

Program for address linkmvs…

Thanks to David Crayford for his assistance in this.

With address linkmvs the specified parameters are treated as variables and their values substituted. If a variable does not exist with the name, the value is passed as-is.

On entry register 1 points to a list of pointers to data. The last element in the list has the top bit on. Process the list until the top bit is on. For example for the parameter list with values “AAA BB C” (which are not substituted)

  • addr1 -> 0X0003″AAA”
  • addr2 -> 0X0002″BB”
  • *addr3 -> 0x001″C”

where * has the top bit on.

If there are no parameters the parameter list is

  • *addr -> 0x0000…
#pragma runopts(plist(os)) 
#define EOL(a) (((unsigned int)a) & 0x80000000)

struct plist {
short len;
char parm[0];
};
int main() {
for ( i = 0; ; i++ ) {
struct plist *p = __osplist[i];
if ( p->len ==0 ) printf("parm %i is Null\n",i);
if ( p->len > 0 )
printf( "parm %i >%.*s<\n",i, p->len, p->parm );
if ( EOL(__osplist[i]) ) break;
}

Where __osplist is a special #define for the parameters based off register 1.

Return code

In both cases you can use the C return … to return an integer value.

Calling C from Rexx – accessing variables.

Usually your program can access variables in the calling Rexx program. You can get, set or delete variables. It is sometimes more complex that the documentation implies.

If your program is called from ISPF you can also set and get ISPF variables, or use ISPF tables to pass data.

To use the Rexx variable interface the applications need access to the ENVironmentBlock (ENVB).

Getting to the ENVB

The Rexx documentation describes how this is passed in register 0, unfortunately a C program does not have access to register 0 (without writing some assembler glue code).

You can get the environment block by calling IRXINIT and passing the parameter “FINDENVB”.
I was unable to use fetch() to dynamically load IRXINIT. (It may work – I couldn’t get it to). Initially I user the binder to include the IRXINIT code, but this is not good practice as you should use the version from the system you are running on.

A better way based on code from David Crayford (thank you) is

#include <stdio.h>                     
#include <stdlib.h>
#include <string.h>
// specify how the irxinit routine is called
#pragma linkage(tsvt_rexxfunc_t,OS)

int main( int argc, char **argv ) {
struct envblock * pEnv;
int rc;
// the TSO anchor block
struct TSVT {
char dummy[140];
char * irxinit;
};

#pragma pack(1)
// this defines a function with parmlist(char *... )
// returning an int
typedef int tsvt_rexxfunc_t( char *, ... );

typedef struct tsvt TSVT;
// TSTV comes from ikjtstv - but no C header equivalent
// so fake one up.
struct tsvt {
int padding[35];
tsvt_rexxfunc_t *irxinit; // Address of IRXEXEC
};
#pragma pack(reset)

int rc2;
// now chain through the control blocks to find the rexx init
// cvtmap provided in SYS1.SIEAHDR.H(CVT)
#define CVTPTR 16L
struct cvtmap * cvt =*( (struct cvtmap ** ) CVTPTR);
// Comment: I think the *((xxx **)) is so unnatural, and always
// get it wrong.

// TSTV comes from ikjtstv - but no C header equivalent
TSVT * tsvt = cvt->cvttvt;
tsvt->irxinit("FINDENVB ",
0, //
0, // instor plist
0, // 4 user field
0, // 5 reserved
&pEnv , // 6 ->envblock
&rc2); // rexx parm 7 return code
printf(" rc2 %i\n",rc2);
}

Set a symbol

This took me a couple of hours to get right. The documentation is not clear in places.

char dummy; 
struct shvblock shv;
memset(&shv,0,sizeof(shv));
char * pSymbol = "COLINSSYMBOL";
char * pValue ="VALUECP";
shv. shvcode = 'S'; // SHVSTORE; // symbolic name set
shv. shvnama = pSymbol; // a symbolic name
shv. shvnaml = strlen(pSymbol); // Len symbolic name
shv. shvvala = pValue ;
shv. shvvall = strlen(pValue);
int rc3;
struct irxexte * pExte = (struct irxexte * ) pEnv-> envblock_irxexte;
tsvt_rexxfunc_t * fptr = (tsvt_rexxfunc_t *) pExte -> irxexcom;

rc = (fptr)("IRXEXCOM",
&dummy,
&dummy,
&shv,
&pEnv,
rc3);
rc2 = shv.shvret;
printf("post rc %i rc2 %i rc3 %i\n",rc,rc2,rc3);

Notes:

The Rexx header file provides

#define  SHVSTORE  "S"             /* Set variable from given value          */    

but you cannot use this because shv. shvcode expects a char ‘S’ , not “S”.

tsvt_rexxfunc_t is used to define the function at address fptr as a z/OS routine with parameter list in register 1, and the high end bit of the last parameter turned on.

After this executed, and the program returned, the Rexx “say COLINSSYMBOL” printed “VALUECP” so it was a success.

A slightly harder case of setting a value.

I put the above code into a subroutine so I was able to use

setSymbol('S',"COLINSSYMBOL","VALUECP");

You can use option upper case ‘S’ which takes the string you give it, and makes a Rexx variable, or you can use the lower case ‘s’ option, which says it does variables substitution.

Uppercase: (The Direct interface). No substitution or case translation takes place. Simple symbols must be valid REXX variable names (that is, in uppercase and not starting with a digit or a period), but in compound symbols any characters (including lowercase, blanks, and so on) are permitted following a valid REXX stem.

This is not entirely true.

With upper case ‘S’

With setSymbol(“MYKEY.aaa“,”VALUECP”), Rexx displayed “MYKEY.AAA” showing the variable did not exist, even though the call to defined it worked successfully.

With setSymbol(“MYKEY.AAA“,”VALUECP”), Rexx displayed “VALUECPA” showing the correct value.

If you are using ‘S’ then always specify the name in upper-case despite what the documentation says.

With lower case ‘s’

Both

setSymbol("MYKEY.aaa","VALUECPA"); 
setSymbol("mykey.bbb","VALUECPA");

worked.

But it gets more complex…

I had a small Rexx program:

/* REXX */
A = "COLINA"
address link CPLINK "A B C "
drop A
say value("MYKEY.A")
say value("MYKEY.B")
say value("MYKEY.COLINA")
say value("A")
say value("SMYKEY.A")
say value("SMYKEY.B")
say value("SMYKEY.COLINA")

If value(“MYKEY.A”) is “MYKEY.A” then there is no variable with that name.

and my program had

setSymbol('S',"MYKEY.A","BIGSA"); 
setSymbol('S',"MYKEY.B","BIGSB");
setSymbol('s',"SMYKEY.A","SMALLSA");
setSymbol('s',"SMYKEY.B","SMALLSB");

The output had

  1. say value(“MYKEY.A”) -> “BIGSA” from my program
  2. say value(“MYKEY.B”) -> “BIGSB” from my program
  3. say value(“MYKEY.COLINA”) -> “MYKEY.COLINA” not a variable
  4. say value(“SMYKEY.A”) -> “SMYKEY.A” not a variable
  5. say value(“SMYKEY.B”) -> “SMALLSB” set from my program
  6. say value(“SMYKEY.COLINA”) -> “SMALLSA” ‘.A’ was substituted with COLINA as part of the set call
  • Lines 1-3 show that there was no substitution of variables.
  • Lines 4 shows that variable SMKEY.A was not created; SMKEY.COLINA was substituted
  • Line 5 had no substitution and was like line 2
  • Line 6 this is the variable name used.

This means that if you specify a lower case ‘s’, the output may not be as you expect. I would suggest you use upper case ‘S’ unless you know what you are doing.

Using Rexx under z/OS Unix Services to display thread information

I wanted to display information about threads running in a big Java application, and see what was executing during set up.

Rexx can provide information on threads, and so I was able to create a script which provided process thread data. There was documentation, but it was not very clear, so I’m documenting what I learned

My program

/* rexx */ 
do k = 1 to 20
call procinfo
say "jobname asid ppid pid threadid tcb cmdline"
do i=1 to bpxw_pid.0
x =procinfo(bpxw_pid.i,'process')
if x = '' then iterate
if bpxw_LOGNAME.i <> "ZWESVUSR" then iterate
y = procinfo(bpxw_pid.i,'thread')
if y = '' then iterate
do j=1 to bpxw_threads
xtcb = d2x( bpxw_TCB.j)
say bpxw_JOBNAME d2x(bpxw_ASID) right(bpxw_PPID,8),
right(bpxw_PID,8) bpxw_THREAD_ID.j xtcb bpxw_CMDLINE
end
end
sleep(1)
end
  • call procinfo returns a list of process ids in a stem bpxw_pid. and userids in a stem bpxw_LOGNAME
  • do i=1 to bpxw_pid.0 iterate through the list of the processes
  • x =procinfo(bpxw_pid.i,’process’) get the process information about the process id in bpxw_pid.i.
  • if x = ” then iterate if the thread no longer exists – do the next one
  • if bpxw_LOGNAME.i <> “ZWESVUSR” then iterate ignore threads from other userids
  • y = procinfo(bpxw_pid.i,’thread’) get the thread information for the process id in bpxw_pid.i.
  • if y = ” then iterate if no data is returned skip this
  • do j=1 to bpxw_threads for each thread in the process …
  • xtcb = d2x( bpxw_TCB.j) convert the thread TCB from decimal to hex.
  • say …
    • bpxw_JOBNAME this is from the process information
    • d2x(bpxw_ASID) display the ASID of the process in hex
    • bpxw_THREAD_ID.j the thread id.

Rexx to C to Rexx sample code

I’ve put up on github some sample code to demonstrate how you can write a function in C, and invoke it from Rexx. I’ve provided some glue code as Rexx uses R0 and R1 to pass parameters, and C programs only use R1.

I’ve create some small functions to use in your C program which hide the Rexx logic. For example

rc = CRexxDrop(pEnv,”ZDROP”);
rc = CRexxGet(pEnv,”InSymbol”,&buffer[0],&lBuffer);
rc = CRexxPut(pEnv,”CPPUTVar,”Colinsv”,0);
Iterate through all symbols

If you have any comments or suggestions, please let me know.

Writing system exits in C (and compiling them).

I wanted to call a C program from Rexx to do some special processing. The C programming guide gave me some hints, but I found it was a struggle to do it. It reminded me of when I was young and my father gave me a “beginners electronics kit” where had transistors, resisters, etc. You could build a “computer” that counted to 3, and make a radio. Unfortunately the instructions that came in it were in German, and for a different model kit to what I had. As a result it was very difficult to get working, but once you knew it was easy.

In the C programming guide there were instruction like “The CSECT must be the module entry point.” without saying which CSECT to use. They gave some sample programs, but not the JCL to compile them. After many failures, (looking at dumps and traces) I found you had to compile the C programs with “NORENT” which went against many years of experience.

I was using the System Programming C facility, which can be used, for example as z/OS exits. Note: This is different to Metal C, which allows you to include assembler code in your C program.

Some background

  • These programs do not have a main() but are invoked with a z/OS type parameter list.
  • They can use C facilities, such as printf, but not LE functions.
  • You cannot use the UNIX file system functions.
  • They need to be called with the C environment set up. You cannot just branch to the entry point.
  • You can have several functions in the same source file. You branch to the one of interest.

Simple case

My C program was

#pragma environment(CPPROGH)
#pragma csect (CODE, “OEMPUT”)
int CPPROGH(int * p, evalblock * pEval, char * env) {
….
return 0;
}

The pragma environment said set up the C environment before calling executing this function. It takes the standard z/OS parameter list.

I needed some glue code to take the parameters from Rexx and store them in a parameter list for the function.

This glue codes saves parameters from R0,and 16(r1) and 20 (r1), then executes the function.

ENVA RMODE ANY
ENVA AMODE 31 
ENVA  CSECT
  ...   
  L    R3,16(R1)  a(Parmlist) 
  ST   R3,Parmlist+0 
  L    R3,20(R1)  a(evalblk) 
  L    R3,0(R3) 
  ST   R3,Parmlist+4 
  ST   R0,PARMLIST+08  A(env block) 
  OI   PARMLIST+08,X'80' 
  la   r1,parmlist 
  L     R15,=V(CPPROGH) 
  BASR  R14,R15 

I wanted this to be called from REXX, which passes parameters in R0 and R1, so I had to write some glue code to store the parameters in storage before passing them to the program.

I compiled the glue code with

//GLUE EXEC PGM=ASMA90,PARM=’DECK,NOOBJECT,LIST,XREF(SHORT),NORENT’,
// REGION=0M
//SYSLIB DD DISP=SHR,DSN=CEE.SCEEMAC
// DD DSN=SYS1.MACLIB,DISP=SHR
//SYSUT1 DD UNIT=SYSDA,SPACE=(CYL,(1,1))
//SYSPUNCH DD DISP=SHR,DSN=COLIN.C.REXX.OBJ(GLUE2)
//SYSPRINT DD SYSOUT=*
//SYSIN DD DISP=SHR,DSN=COLIN.C.REXX(GLUE2)
//*

and compiled the C code with

//S1 JCLLIB ORDER=CBC.SCCNPRC
// SET LOADLIB=COLIN.C.REXX.LOAD
// SET LIBPRFX=CEE
//COMPILE EXEC PROC=EDCCB,
// LIBPRFX=&LIBPRFX,
// CPARM=’OPTFILE(DD:SYSOPTF),NORENT‘,
// BPARM=’SIZE=(900K,124K),RENT,LIST,XREF,RMODE=ANY,AMODE=31′
//COMPILE.SYSOPTF DD DISP=SHR,DSN=COLIN.C.REXX(CPARMS)
//COMPILE.SYSIN DD DISP=SHR,DSN=COLIN.C.REXX(CPPROGHE)
//BIND.SYSLMOD DD DISP=SHR,DSN=&LOADLIB.
//BIND.SYSLIB DD DISP=SHR,DSN=CEE.SCEESPC
// DD DISP=SHR,DSN=CEE.SCEELKED
//BIND.OBJLIB DD DISP=SHR,DSN=COLIN.C.REXX.OBJ
//BIND.SYSIN DD *
INCLUDE OBJLIB(GLUE2)
ENTRY ENVA
NAME COLIN(R)
/*

The EDCCB procedure to compile and bind, stores the object deck in a temporary file then passes this file and BIND.SYSIN into the binder.

C persistent environment.

The previous example created a C environment, ran my program, and deleted the C environment. If you want to do many calls to C functions you can set up a Persistent C environment. In this environment you do

  • From assembler, set up the environment
  • From assembler, use the environment, and call functions with your program as many times as you need
  • From assembler close down the environment,

This is well documented in the C programming guide, (but not how to compile it).

The essence of my program was

Set up the environment

L R15,=V(EDCXHOTL)
BASR R14,R15

Call my function

   LA R4,HANDLE 
   LA R5,USEFN  This has the  
   STM  R4,R5,PARMLIST 
* now the user paramaters
  ...
   OI   PARMLIST+16,X'80' 
   LA   R1,PARMLIST 
   L    R15,=V(EDCXHOTU) 
   BASR R14,R15 
...
USEFN    DC V(CPPROGH) <<  This function name

Clean up

    LA R1,PARMLIST 
    OI 0(R1),X'80' 
    L R15,=V(EDCXHOTT) 
    BASR R14,R15 

My C program was

#pragma linkage(CPPROGH,OS)
int CPPROGH(int * p, evalblock * pEval, char * env) {
printf(“in CPPROG\n”);
return 0}

In this case the pragma is LINKAGE(CPPROGH,OS). The previous, self contained code, had ENVIRONMENT(CPPROGH). You need to use the right one.

Which procedure do I use to compile?

The C books describe the various procedures, for example EDCCB for compile and BIND, and EDCCL for compile and LINKEDIT. They do the same thing. The LINKEDIT uses program HEWL to link edit. The BIND uses IEWL to invoke the binder. These are both aliases to the binder IEWBLINK.

What’s the difference between BALR and BASR?

When coding, my fingers automatically used BALR (Branch and Link Register). This worked fine, but I should have used BASR (Branch and Save Register). As the Principles of Operation (POP) says

It is recommended, however, that BRANCH AND SAVE (BAS and BASR) be used instead and that BRANCH AND LINK be avoided since it places nonzero information in bit positions 32-39 of the general register in the 24-bit addressing mode, which may lead to problems and may decrease performance.

In 31 bit mode with BALR 14,15, the return address is stored in register 14. ‘1’ followed by the 31 it address.

In 24 bit mode, the return address has other information at the top, including the condition code. Most of the time this information will be ignored.

So using BALR is not wrong, it is that BASR is better.