HPlogo HP Data Entry and Forms Management System (VPLUS) Reference Manual: HP 3000 MPE/iX Computer Systems > Chapter 6 USING VPLUS INTRINSICS

CALLING VPLUS INTRINSICS

» 

Technical documentation

Complete book in PDF
» Feedback

 » Table of Contents

 » Index

The examples in Table 6-2 “Examples of Intrinsic Call Formats for Each Language” show the format for calls to the VPLUS intrinsics from each language, where:

intrinsicname

Identifies the intrinsic being called.

parameter

At least one parameter is required for each intrinsic; the particular parameters are listed in the formats for the individual intrinsic descriptions.

Table 6-2 Examples of Intrinsic Call Formats for Each Language

Language

Intrinsic Call Format

COBOL

CALL "intrinsicname" USING parameter1 [, parameter2]...

FORTRAN

CALL intrinsicname (parameter1 [,parameter2]...)

BASIC

label CALL intrinsicname(parameter1[,parameter2]...)

PASCAL

intrinsicname(parameter1[,parameter2]...);

SPL

intrinsicname(parameter1[,parameter2]...);

 

In order to provide consistency between calls from different programming languages, the following rules apply to all parameters:

  • Parameters are passed by reference; this means that a literal value cannot be used as a parameter. The exception is VSETLANG, which has one parameter that is passed by value.

  • No condition codes are returned; the status of the call is returned in a status word included as part of the comarea parameter specified in every intrinsic call.

  • Return type intrinsics are not allowed; any values returned by the intrinsic are sent to the comarea or to a passed parameter.

Parameter Types

The data types that are used in VPLUS intrinsics are shown in Table 6-3 “Data Types Used for Various Languages” Note that not all types are allowed for all languages.

Table 6-3 Data Types Used for Various Languages

Data Type

COBOL

FORTRAN

BASIC

PASCAL

SPL

Character

DISPLAY PIC X(n)

Character

String

Packed Array of Char

Byte Array

Two-byte Integer

COMP PIC S9 thru PIC S9(4)

Integer*2

Integer

Subrange -32768.. 32767

Integer

Unsigned Two-byte Integer

COMP PIC 9 thru PIC 9(4)

Logical

Integer (with value <32767)

Subrange 0..65535

Logical

Four-byte Integer

COMP PIC S9(5) thru PIC S9(9)

Integer*4

Integer Integer1

Integer

Double

Real Four-byte

Real

Real

Real

Real

Long 8-byte

Double Precision

Long

Longreal

Long

1In BASIC, a double integer can be represented by two consecutive integers:

  • the first contains the high-order digits of values above 32767 or is zero,

  • the second contains the low-order digits of values above 32767 or the entire value up to 32767.

 

The VPLUS parameters use only data types that are available in all programming languages: character, integer, logical, and double integer. The only exceptions are the transfer and conversion intrinsics, VPUTtype and VGETtype, which use real and long.

Each parameter is described according to its generic type (character, integer, logical, or double integer). This table is provided for those languages that do not call their data types by these particular names. For example, if you are coding in COBOL and a parameter is specified as logical, you can determine from this table that it is an unsigned computational item that uses from one to four digits.

Feedback to webmaster