|
OpenVMS Programming Concepts Manual
- The C language header file
starlet.h
defines OpenVMS system services entry points. The file
lib$routines.h
declares the LIB$ Run-Time Library routines.
- The structure of an item list entry is
defined.
- The $DESCRIPTOR macro declares and
initializes a character string descriptor. Here, two descriptors are
created for use with the
sys$trnlnm
system service.
- The function
sizeof
is used to obtain the size of the string. The returned length will be
stored as a short integer in
return_length
.
- The
sys$trnlnm
routine is defined in
starlet.h
.
- The IF statement performs a logical test
following the function reference to determine whether the service
completed successfully. If an error or warning occurs during the
service call, the error is signaled.
Example 20-6 System Service Call in COBOL |
IDENTIFICATION DIVISION.
PROGRAM-ID. ORION. (1)
ENVIRONMENT DIVISION.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 TABNAM PIC X(11) VALUE "LNM$FILE_DEV".
01 CYGDES PIC X(6) VALUE "CYGNUS".
01 NAMDES PIC X(255) VALUE SPACES. (2)
01 NAMLEN PIC S9(4) COMP.
01 ITMLIS.
02 BUFLEN PIC S9(4) COMP VALUE 225.
02 ITMCOD PIC S9(4) COMP VALUE 2. (3)
02 BUFADR POINTER VALUE REFERENCE NAMDES.
02 RETLEN POINTER VALUE REFERENCE NAMLEN.
02 FILLER PIC S9(5) COMP VALUE 0.
01 RESULT PIC S9(9) COMP. (4)
PROCEDURE DIVISION.
START-ORION.
CALL "SYS$TRNLNM" (5)
USING OMITTED
BY DESCRIPTOR TABNAM
BY DESCRIPTOR CYGDES (6)
OMITTED
BY REFERENCE ITMLIS
GIVING RESULT.
IF RESULT IS FAILURE (7)
GO TO ERROR-CHECK.
DISPLAY "NAMDES: ", NAMDES(1:NAMLEN).
GO TO THE-END.
ERROR-CHECK.
DISPLAY "Returned Error: ", RESULT CONVERSION.
THE-END.
STOP RUN.
|
COBOL Notes
- The PROGRAM-ID paragraph identifies the
program by specifying the program name, which is the global symbol
associated with the entry point. The compiler builds the entry mask.
- Enough bytes are allocated for the
alphanumeric output data. The compiler generates a descriptor when you
specify USING BY DESCRIPTOR in the CALL statement.
- The value of the symbolic code LNM$STRING is
2. Section 20.4.5 explains how to obtain values for symbolic codes.
- This definition reserves a signed longword
with COMP (binary) usage to receive the output value.
- The service is called by the SYS$ form of the
service name, and the name is enclosed in quotation marks.
Specify
arguments in positional order only, with the USING statement. You
cannot omit arguments; if you are accepting the default for an
argument, you must pass the default value explicitly (OMITTED in this
example). You can specify explicitly how each argument is being
passed: by descriptor, by reference (that is, by address), or by value.
You can also implicitly specify how an argument is being passed:
through the default mechanism (by reference), or through association
with the last specified mechanism (thus, the last two arguments in the
example are implicitly passed by value).
- The input string is defined as alphanumeric
(ASCII) data. The compiler generates a descriptor when you specify
USING BY DESCRIPTOR in the CALL statement.
- The IF statement tests RESULT for a failure
status. In this case, control is passed to the routine ERROR-CHECK.
Example 20-7 System Service Call in
FORTRAN |
SUBROUTINE ORION
IMPLICIT NONE ! Require declaration of all symbols
INCLUDE '($SYSSRVNAM)' ! Declare system service names (1)
INCLUDE '($LNMDEF)' ! Declare $TRNLNM item codes
INCLUDE '(LIB$ROUTINES)' ! Declare LIB$ routines
STRUCTURE /ITEM_LIST_3_TYPE/ ! Structure of item list (2)
INTEGER*2 BUFLEN ! Item buffer length
INTEGER*2 ITMCOD ! Item code
INTEGER*4 BUFADR ! Item buffer address
INTEGER*4 RETADR ! Item return length address
END STRUCTURE
RECORD /ITEM_LIST_3_TYPE/ ITEMLIST(2) ! Declare itemlist
CHARACTER*255 EQUIV_NAME ! For returned equivalence name
INTEGER*2 NAMLEN ! For returned name length
VOLATILE EQUIV_NAME,NAMLEN (3)
INTEGER*4 STATUS ! For returned service status (4)
! Fill in itemlist
!
ITEMLIST(1).ITMCOD = LNM$_STRING
ITEMLIST(1).BUFLEN = LEN(EQUIV_NAME) (5)
ITEMLIST(1).BUFADR = %LOC(EQUIV_NAME)
ITEMLIST(1).RETADR = %LOC(NAMLEN)
ITEMLIST(2).ITMCOD = 0 ! For terminator
ITEMLIST(2).BUFLEN = 0
! Call SYS$TRNLM
!
STATUS = SYS$TRNLNM (, ! ATTR omitted (6)
1 'LNM$FILE_DEV', ! TABNAM
2 'CYGNUS', ! LOGNAM
3 , ! ACMODE omitted
4 ITEMLIST) ! ITMLST
! Check return status, display translation if successful
!
IF (.NOT. STATUS) THEN (7)
CALL LIB$SIGNAL(%VAL(STATUS))
ELSE
WRITE (*,*) 'CYGNUS translates to: "',
1 EQUIV_NAME(1:NAMLEN), '"'
END IF
END
|
FORTRAN Notes
- The module $SYSSRVNAM in the FORTRAN system
default library FORSYSDEF.TLB contains INTEGER and EXTERNAL
declarations for each of the system services, so you need not
explicitly provide these declarations in your program. Module $LNMDEF
defines constants and data structures used when calling the logical
name services, and module LIB$ROUTINES contains declarations for the
LIB$ Run-Time Library routines.
- The structure of an OpenVMS 3-longword item
list is declared and then used to define the record variable ITEM_LIST.
The second element will be used for the terminator.
- The VOLATILE declaration is required for
variables that are modified by means other than a direct assignment or
as an argument in a routine call.
- Return status variables should always be
declared as longword integers.
- The LEN intrinsic function returns the
allocated length of EQUIV_NAME. The %LOC built-in function returns the
address of its argument.
- By default, FORTRAN passes arguments by
reference, except for strings which are passed by CLASS_S descriptor.
Arguments are omitted in FORTRAN by leaving the comma as a placeholder.
All arguments must be specified or explicitly omitted.
- A condition value can be tested for success
or failure by a true/false test. For more information on testing return
statuses, see the OpenVMS FORTRAN documentation.
Example 20-8 System Service Call in
Pascal |
[INHERIT('SYS$LIBRARY:STARLET', (1)
'SYS$LIBRARY:PASCAL$LIB_ROUTINES')]
PROGRAM ORION (OUTPUT);
TYPE
Item_List_Cell = RECORD CASE INTEGER OF (2)
1:( { Normal Cell }
Buffer_Length : [WORD] 0..65535;
Item_Code : [WORD] 0..65535;
Buffer_Addr : UNSIGNED;
Return_Addr : UNSIGNED
);
2:( { Terminator }
Terminator : UNSIGNED
);
END;
Item_List_Template(Count:INTEGER) = ARRAY [1..Count] OF Item_List_Cell;
VAR
Item_List : Item_List_Template(2);
Translated_Name : [VOLATILE] VARYING [255] OF CHAR; (3)
Status : INTEGER;
BEGIN
{ Specify the buffer to return the translation } (4)
Item_List[1].Buffer_Length := SIZE(Translated_Name.Body);
Item_List[1].Item_Code := LNM$_String;
Item_List[1].Buffer_Addr := IADDRESS(Translated_Name.Body);
Item_List[1].Return_Addr := IADDRESS(Translated_Name.Length);
{ Terminate the item list }
Item_List[2].Terminator := 0;
{ Translate the CYGNUS logical name }
Status := $trnlnm(Tabnam := 'LNM$FILE_DEV', Lognam := 'CYGNUS', (5)
Itmlst := Item_List);
IF NOT ODD(Status) (6)
THEN
LIB$SIGNAL(Status)
ELSE
WRITELN('CYGNUS is equivalent to ',Translated_Name);
END.
|
Pascal Notes
- The Pascal environment file STARLET.PEN
defines OpenVMS system services, data structures and constants.
PASCAL$LIB_ROUTINES declares the LIB$ Run-Time Library routines.
- The structure of an item list entry is
defined using a variant record type.
- The VARYING OF CHAR type is a
variable-length character string with two components: a word-integer
length and a character string body, which in this example is 255 bytes
long. The VOLATILE attribute is required for variables that are
modified by means other than a direct assignment or as an argument in a
routine call.
- The functions SIZE and IADDRESS obtain the
allocated size of the string body and the address of the string body
and length. The returned length will be stored into the length field of
the varying string Translated_Name, so that it will appear to be the
correct size.
- The definition of the SYS$TRNLNM routine in
STARLET.PEN contains specifications of the passing mechanism to be used
for each argument; thus, it is not necessary to specify the mechanism
here.
- The IF statement performs a logical test
following the function reference to see if the service completed
successfully. If an error or warning occurs during the service call,
the error is signaled.
Example 20-9 System Service Call in VAX
MACRO |
CYGDES: .ASCID /CYGNUS/ (1) ; Descriptor for CYGNUS string
TBLDES: .ASCID /LNM$FILE_DEV/ (2) ; Logical name table
NAMBUF: .BLKB 255 (3) ; Output buffer
NAMLEN: .BLKW 1 (4) ; Word to receive length
ITEMS: .WORD 255 ; Output buffer length
.WORD LNM$STRING ; Item code
.ADDRESS - ; Output buffer
NAMBUF
.ADDRESS - ; Return length
NAMLEN
.LONG 0 ; List terminator
.
.
.
.ENTRY ORION,0 (5) ; Routine entry point & mask
$TRNLNM_S - (6)
TABNAM=TBLDES, -
LOGNAM=CYGDES, -
ITMLST=ITEMS
BLBC R0,ERROR (7) ; Check for error
.
.
.
.END
|
VAX MACRO Notes
- The input character string descriptor
argument is defined using the .ASCID directive.
- The name of the table to search is defined
using the .ASCID directive.
- Enough bytes to hold the output data are
allocated for an output character string argument.
- The MACRO directive .BLKW reserves a word to
hold the output length.
- A routine name and entry mask show the
beginning of executable code in a routine or subroutine.
- A macro name that has the suffix _S or _G
calls the service.
You can specify arguments either by keyword (as
in this example) or by positional order. (Keyword names correspond to
the names of the arguments shown in lowercase in the system service
format descriptions in the OpenVMS System Services Reference Manual.) If you omit any optional
arguments (if you accept the defaults), you can omit them completely if
you specify arguments by keyword. If you specify arguments by
positional order, however, you must specify the comma for each missing
argument. Use the number sign (#) to indicate a literal value for
an argument.
- The BLBC instruction causes a branch to a
subroutine named ERROR (not shown) if the low bit of the condition
value returned from the service is clear (low bit clear = failure or
warning). You can use a BSBW instruction to branch unconditionally to a
routine that checks the return status.
Chapter 21 STARLET Structures and Definitions for C Programmers
This chapter describes the libraries that contain C header files for
routines supplied by the OpenVMS Alpha operating system.
21.1 SYS$STARLET_C.TLB Equivalency to STARLETSD.TLB
The SYS$STARLET_C.TLB file, which was introduced in OpenVMS Alpha
Version 1.0, contains all the .H files that provide STARLET
functionality equivalent to STARLETSD.TLB. The file SYS$STARLET_C.TLB,
together with DECC$RTLDEF.TLB
that ships with the Compaq C Compiler, replaces VAXCDEF.TLB that
previously shipped with the VAX C Compiler. DECC$RTLDEF.TLB contains
all the .H files that support the compiler and RTL, such as STDIO.H.
If you are running an application from a release prior to OpenVMS Alpha
Version 1.0, the following differences may require source changes:
-
RMS structures
Previously, the RMS structures FAB, NAM, RAB,
XABALL, and so forth, were defined in the appropriate .H files as
"struct RAB {...", for example. The .H files supplied in
OpenVMS Alpha Version 1.0 define them as "struct rabdef
{...". To compensate for this difference, lines of the form
"#define RAB rabdef" have been added. However, there is one
situation where a source change is required because of this change. If
you have a private structure that contains a pointer to one of these
structures and your private structure is defined (but not used) before
the RMS structure has been defined, you will receive compile-time
errors similar to the following:
%CC-E-PASNOTMEM, In this statement, "rab$b_rac" is not a member of "rab".
|
This error can be avoided by reordering your source file so that
the RMS structure is defined before the private structure. Typically,
this involves moving around "#include" statements.
- LIB (privileged interface) structures
Historically, three
structures from LIB (NFBDEF.H, FATDEF.H, and FCHDEF.H) have been made
available as .H files. These files were shipped as .H files in OpenVMS
Alpha Version 1.0 and 1.5 (not in the new SYS$STARLET_C.TLB). As of
OpenVMS Alpha Version 1.0, the file SYS$LIB_C.TLB, containing all LIB
structures and definitions, has been added. These three .H files are
now part of that .TLB and are no longer shipped separately. Source
changes may be required, because no attempt has been made to preserve
any existing anomalies in these files. The structures and definitions
from LIB are for privileged interfaces only and are therefore subject
to change.
- Use of "variant_struct" and "variant_union"
In the new .H files, variant_struct and variant_union are always used;
whereas previously some structures used struct and union. Therefore,
the intermediate structure names cannot be specified when referencing
fields within data structures.
For example, the following statement:
AlignFaultItem.PC[0] = DataPtr->afr$r_pc_data_overlay.afr$q_fault_pc[0];
|
becomes:
AlignFaultItem.PC[0] = DataPtr->afr$q_fault_pc[0];
|
- Member alignment
Each of the .H files in SYS$STARLET_C.TLB
saves and restores the state of "#pragma member_alignment".
- Conventions
The .H files in SYS$STARLET_C.TLB adhere to some conventions that were
only partly followed in VAXCDEF.TLB. All constants (#defines) have
uppercase names. All identifiers (routines, structure members, and so
forth) have lowercase names. Where there is a difference from
VAXCDEF.TLB, the old symbol name is also included for compatibility,
but users are encouraged to follow the new conventions.
- Use of Librarian utility to access the .H files
During
installation of OpenVMS Alpha Version 1.0, the contents of
SYS$STARLET_C.TLB are not extracted into the separate .H files. The
Compaq C
Compiler accesses these files from within SYS$STARLET_C.TLB, regardless
of the format of the #include statement. If you want to inspect an
individual .H file, you can use the Librarian utility, as in the
following example:
$ LIBRARY /EXTRACT=AFRDEF /OUTPUT=AFRDEF.H SYS$LIBRARY:SYS$STARLET_C.TLB
|
- Additional .H files included in SYS$STARLET_C.TLB
In addition
to the .H files derived from STARLET sources, SYS$STARLET_C.TLB
includes .H files that provide support for POSIX Threads Library, such
as CMA.H.
21.2 NEW STARLET Definitions for C
As of OpenVMS Alpha Version 7.0, SYS$LIBRARY:SYS$STARLET_C.TLB (or
STARLET) provides C function prototypes for system services, as well as
new and enhanced data structure definitions. The new definitions are
more consistent with the OpenVMS C language coding conventions and
definitions (typedefs) used in SYS$LIBRARY:SYS$LIB_C.TLB.
To maintain source compatibility for existing users of STARLET.H, the
"old style" function declarations and definitions are still
provided by default. To take advantage of the new system service
function prototypes and type definitions, you must explicitly enable
them.
You can define the __NEW_STARLET symbol with a Compaq C command line
qualifier or include the definition directly in your source program.
For example:
- Define the _NEW_STARLET symbol with the Compaq C command line
qualifier as follows:
/DEFINE=(__NEW_STARLET=1)
|
or
- Define the _NEW_STARLET symbol in your C source program before
including the SYS$STARLET_C.TLB header files:
#define __NEW_STARLET 1
#include <starlet.h>
#include <vadef.h>
|
To see the currently available system service function prototypes in
STARLET.H, you can use the Librarian utility as shown in the following
example:
$ LIBRARY/OUTPUT=STARLET.H SYS$LIBRARY:SYS$STARLET_C.TLB/EXTRACT=STARLET
|
The following example shows a new system service function prototype as
it is defined in STARLET.H:
#pragma __required_pointer_size __long
int sys$expreg_64(
struct _generic_64 *region_id_64,
unsigned __int64 length_64,
unsigned int acmode,
unsigned int flags,
void *(*(return_va_64)),
unsigned __int64 *return_length_64);
#pragma __required_pointer_size __short
|
For more information about Compaq C pointer size pragmas, see the
DEC C User's Guide for OpenVMS Systems.
The following source code example shows the sys$expreg_64 function
prototype referenced in a program.
#define __NEW_STARLET 1 /* Enable "New Starlet" features */
#include <starlet.h> /* Declare prototypes for system services */
#include <gen64def.h> /* Define GENERIC_64 type */
#include <vadef.h> /* Define VA$ constants */
#include <ints.h> /* Define 64-bit integer types */
#include <far_pointers.h> /* Define 64-bit pointer types */
{
int status; /* Ubiquitous VMS status value */
GENERIC_64 region = { VA$C_P2 }; /* Expand in "default" P2 region */
VOID_PQ p2_va; /* Returned VA in P2 space */
uint64 length; /* Allocated size in bytes */
extern uint64 page_size; /* Page size in bytes */
status = sys$expreg_64( ®ion, request_size, 0, 0, &p2_va, &length );
...
}
|
Table 21-1 lists the data structures that are used by the new
function protypes.
Table 21-1 Structures Used by_NEW_STARLET Prototypes
Structure Used by Prototype |
Defined by Header File |
Common Prefix for Structure Member Names |
Description |
struct _cluevthndl
|
cluevtdef.h
|
cluevthndl$
|
Cluster event handle
|
struct _fabdef
|
fabdef.h
|
fab$
|
File access block
|
struct _generic_64
|
gen64def.h
|
gen64$
|
Generic quadword structure
|
struct _ieee
|
ieeedef.h
|
ieee$
|
IEEE Floating point control structure
|
struct _ile2
1
|
iledef.h
|
ile2$
|
Item list entry 2
|
struct _ile3
1
|
iledef.h
|
ile3$
|
Item list entry 3
|
struct _iosa
|
iosadef.h
|
iosa$
|
I/O status area
|
struct _iosb
|
iosbdef.h
|
iosb$
|
I/O status block
|
struct _lksb
|
lksbdef.h
|
lksb$
|
Lock status block
|
struct _rabdef
|
rabdef.h
|
rab$
|
RMS record access block
|
struct _secid
|
seciddef.h
|
secid$
|
Global section identifier
|
struct _va_range
|
va_rangedef.h
|
va_range$
|
32-bit virtual address range
|
1Use of this structure type is not required by the function
prototypes in starlet.h. This structure type is provided as a
convenience and can be used where it is appropriate.
|