|
HP OpenVMS systems documentation |
Previous | Contents | Index |
Example 20-4 System Service Call in BLISS |
---|
MODULE ORION= BEGIN EXTERNAL ROUTINE ERROR_PROC: NOVALUE; ! Error processing routine LIBRARY 'SYS$LIBRARY:STARLET.L32'; ! Library containing OpenVMS ! macros (including $TRNLNM). ! This declaration ! is required. GLOBAL ROUTINE ORION: NOVALUE= BEGIN OWN NAMBUF : VECTOR[255, BYTE], ! Output buffer NAMLEN : WORD, ! Translated string length ITEMS : BLOCK[16,BYTE] INITIAL(WORD(255, ! Output buffer length LNM$_STRING), ! Item code NAMBUF, ! Output buffer NAMLEN, ! Address of word for ! translated ! string length 0); ! List terminator LOCAL ! Return status from STATUS; ! system service STATUS = $TRNLNM(TABNAM = %ASCID'LNM$FILE_DEV', LOGNAME = %ASCID'CYGNUS', ITMLST = ITEMS); (1) IF NOT .STATUS THEN ERROR_PROC(.STATUS); (2) END; |
Example 20-5 System Service Call in C |
---|
#include <starlet.h> (1) #include <lib$routines.h> #include <ssdef.h> #include <lnmdef.h> #include <descrip.h> #include <stdio.h> typedef struct { (2) unsigned short buffer_length; unsigned short item_code; char *buffer_addr; short *return_len_addr; unsigned terminator; } item_list_t; main () { (3) $DESCRIPTOR(table_name, "LNM$FILE_DEV"); $DESCRIPTOR(log_name, "CYGNUS"); char translated_name[255]; int status; short return_length; item_list_t item_list; item_list.buffer_length = sizeof(translated_name); (4) item_list.item_code = LNM$_STRING; item_list.buffer_addr = translated_name; item_list.return_len_addr = &return_length; item_list.terminator = 0; status = sys$trnlnm(0, &table_name, &log_name, 0, &item_list); (5) if (!(status & 1)) (6) lib$signal(status); else printf("The logical name %s is equivalent to %*s\n", log_name.dsc$a_pointer, return_length, translated_name); } |
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. |
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 |
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. |
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 |
This chapter describes the libraries that contain C header files for
routines supplied by the OpenVMS Alpha and OpenVMS I64 operating
systems.
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 HP 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:
%CC-E-PASNOTMEM, In this statement, "rab$b_rac" is not a member of "rab". |
AlignFaultItem.PC[0] = DataPtr->afr$r_pc_data_overlay.afr$q_fault_pc[0]; |
AlignFaultItem.PC[0] = DataPtr->afr$q_fault_pc[0]; |
$ LIBRARY /EXTRACT=AFRDEF /OUTPUT=AFRDEF.H SYS$LIBRARY:SYS$STARLET_C.TLB |
SYS$LIBRARY:SYS$STARLET_C.TLB (or STARLET) provides C function prototypes for system services, as well as data structure definitions. The compiler searches the library file SYS$LIBRARY:SYS$STARLET_C.TLB for the STARLET header files. The definitions are consistent with the OpenVMS C language coding conventions and definitions (typedefs) used in SYS$LIBRARY:SYS$LIB_C.TLB.
To maintain source compatibility for users of STARLET.H as provided prior to OpenVMS Alpha Version 7.0, 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 HP C command line qualifier or include the definition directly in your source program. For example:
/DEFINE=(__NEW_STARLET=1) |
#define __NEW_STARLET 1 #include <starlet.h> #include <vadef.h> |
To see the 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 HP C pointer size pragmas, see the HP 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.
Structure Used by Prototype | Defined by Header File | Common Prefix for Structure Member Names | Description |
---|---|---|---|
struct _acmecb | acmedef.h | acmedef$ | ACM communications buffer |
struct _acmesb | acmedef.h | acmedef$ | ACM status block |
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 _ilea_64 1 | iledef.h | ilea_64$ | 64-bit item list entry A structure |
struct _ileb_64 1 | iledef.h | ileb_64$ | 64-bit item list entry B structure |
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 |
Previous | Next | Contents | Index |