HP 3000 Manuals

Operation (cont.) [ COBOL/HP-UX Operating Guide for the Series 700 and 800 ] MPE/iX 5.0 Documentation


COBOL/HP-UX Operating Guide for the Series 700 and 800

Operation (cont.) 

CBL_JOIN_FILENAME 

Forms a file-name by joining together its component parts; that is, the
path-name, base-name and extension. 

Syntax: 

     CALL "CBL_JOIN_FILENAME" USING split-join-params
                                    join-buffer
                                    path-buffer
                                    basename-buffer
                                    extension-buffer
                              RETURNING status-code

Parameters: 

split-join-params    Group item defined as:

  param-length       PIC X(2) COMP-X.

  split-join-flag1   PIC X COMP-X.

  split-join-flag2   PIC X COMP-X.

  path-offset        PIC X(2) COMP-X.

  path-length        PIC X(2) COMP-X.

  basename-offset    PIC X(2) COMP-X.

  basename-length    PIC X(2) COMP-X.

  extension-offset   PIC X(2) COMP-X.

  extension-length   PIC X(2) COMP-X.

  total-length       PIC X(2) COMP-X.

  split-buf-len      PIC X(2) COMP-X.

  join-buf-len       PIC X(2) COMP-X.

  first-path-        PIC X(2) COMP-X.
component-length

join-buffer          PIC X(n).

path-buffer          PIC X(n).

basename-buffer      PIC X(n).

extension-buffer     PIC X(n).

status-code          See the section Key 

Description: 

The new file-name is formed by concatenating:

   *   the first path-length bytes (starting from path-offset) of
       path-buffer

   *   the first basename-length bytes (starting from basename-offset) of
       basename-buffer

   *   the first extension-length bytes (starting from extension-offset)
       of extension-buffer

and is placed in join-buffer with length total-length.

This routine can be made to fold to upper case by setting the least
significant bit (bit 0) of split-join-flag1.  If this bit is not set, the
case will be preserved.  We recommend that you do not set this flag if
you intend to run your program on UNIX.

This routine can accept either null-terminated or space-terminated
strings.  Setting the second least significant bit (bit 1) of
split-join-flag1 results in the routine expecting null-terminated
strings.  If this bit is not set, space-terminated strings are expected.

The path, base-name, and extension fields can be shorter than the lengths
specified by path-length, basename-length, and extension-length
respectively, if they are terminated with either a space or a null,
depending on the setting of bit 1 of split-join-flag1.

path-buffer, basename-buffer, extension-buffer, and join-buffer do not
have to be four distinct buffers.  This means that this routine can be
used with CBL_SPLIT_FILENAME to replace one component of a file-name.

If path-buffer is not empty and does not have a trailing slash (/), and
basename-buffer is not empty, the routine inserts a "/" between the path
and base-name in join-buffer.

If extension is period (.), the string returned in join-buffer has an
extension of spaces; that is, the file-name has a trailing period.

If total-length is less than join-buf-len, the characters after the
end of the file-name are nulls or spaces depending on bit 1 of
split-join-flag1.

See also File-names in the section "Routines by Category"  earlier in
this chapter and the description of CBL_SPLIT_FILENAME.

Parameters on Entry: 

param-length         Length of split-join-params in bytes, including the
                     two bytes for param-length.  The normal value for
                     param-length is 24.

split-join-flag1     bit 1 - if set, strings are null-terminated;
                     otherwise, strings are space-terminated.  bit 0 - if
                     set, the new file-name is folded to upper case;
                     otherwise, no change.

path-offset          Offset of the start of the path in path-buffer
                     (indexed from one).

path-length          Length of path if not space- or null- terminated.

basename-offset      Offset of the start of the basename in
                     basename-buffer (indexed from one).

basename-length      Length of base-name if not space- or null-
                     terminated.

extension-offset     Offset of the start of the extension in
                     extension-buffer (indexed from one).

extension-length     Length of extension if not space- or null-
                     terminated.

path-buffer          Path-name.

basename-buffer      Base-name.

extension-buffer     Extension.

join-buf-len         Length of join-buffer.

Parameters on Exit: 

total-length         Total number of characters in the file-name.

join-buffer          The joined-up file-name.

status-code          0 = success
                     1 = file-name too big for join-buffer
                     4 = illegal file-name

CBL_LOCATE_FILE 

This routine has two uses.  It can be used to expand an environment
variable in a file specification, where the environment variable contains
a list of several paths.  It can also determine whether an OPEN INPUT
using a particular file specification will find the file in a library or
as a separate disk file. 

Syntax: 

     CALL "CBL_LOCATE_FILE" USING user-file-spec
                                  user-mode
                                  actual-file-spec
                                  exist-flag
                                  path-flag
                            RETURNING status-code

Parameters: 

user-file-spec       PIC X(n).

user-mode            PIC X COMP-X.

actual-file-spec     Group item defined as:

  buffer-len         PIC X(2) COMP-X.

  buffer             PIC X(n).

exist-flag           PIC X COMP-X.

path-flag            PIC X COMP-X.

status-code          See the section Key.

Parameters on Entry: 

user-file-spec       Contains the file-name specification; this can
                     include an embedded environment variable or library
                     name.  For example:

                     standard file-name:

                     path/file-name.ext

                     embedded environment variable:

                     $envname/file-name.ext

                     embedded library name:

                     path/library-name.lbr/file-name.ext

user-mode            Specifies what to do with user-file-spec:

                     0 =   Check whether the file exists in a library or
                           as a separate disk file.

                     If user-file-spec includes an embedded library-name,
                     that library is opened (if it exists) and searched
                     for the file.  The library is left open afterwards.

                     If user-file-spec includes an embedded environment
                     variable, the file will be searched for along each
                     path specified in that variable.  If it is found,
                     actual-file-spec on exit contains the file
                     specification with the environment variable expanded
                     to the successful path.

                     Otherwise, actual-file-spec on exit contains the
                     file specification with the environment variable
                     expanded to the first path it contained.

                     1 =   If user-file-spec includes an environment
                           variable, actual-file-spec on exit contains
                           the file specification with the environment
                           variable expanded to the first path it
                           contained.  The file is not searched for.

                     2 =   If user-file-spec includes an environment
                           variable, actual-file-spec on exit contains
                           the file specification with the environment
                           variable expanded to the next path it
                           contained.  The file is not searched for.
                           This option should only be used after a
                           successful call with user-mode = 1 or 2.  See
                           path-flag below.

path-flag            If user-mode = 2, this data item contains the value
                     that was returned in this item from the previous
                     user-mode = 1 or 2 call.

buffer-len           Size of buffer.

Parameters on Exit: 

buffer               Buffer to contain the resolved file specification,
                     as described under user-mode.  If the resolved file
                     specification is larger than the size specified by
                     buffer-len, buffer remains unchanged and status-code
                     is set accordingly.

exist-flag           If user-mode = 0, this data item on exit shows
                     whether the file specified in user-file-spec exists.

                     0 =   file not found or not searched for

                     1 =   file was found in a library that was already
                           open

                     2 =   file was found in a library specified in
                           user-file-spec

                     3 =   file was found as a separate disk file

                           If user-mode is not 0, then this data item is
                           always 0 on exit.

path-flag            If user-mode = 1, shows whether user-file-spec
                     contained an embedded environment variable that has
                     been expanded in actual-file-spec as follows:

                     0 =   actual-file-spec does not include an expanded
                           environment variable

                     1 =   actual-file-spec contains an expanded
                           environment variable

status-code          Return status:

                     0 =     success

                     1 =     the environment variable does not exist

                     2 =     there is no next path

                     3 =     the resolved file-name is too large for
                             buffer

                     4 =     resulting file-name is illegal

                     255 =   other error

CBL_NLS_CLOSE_MSG_FILE 

This routine is reserved for use on other environments; it has no effect
on UNIX. See Chapter 30 , National Language Support for details on NLS
routines available on UNIX.

Syntax: 

     CALL "CBL_NLS_CLOSE_MSG_FILE" USING  msg-file-handle
                               RETURNING status-code

Parameters: 

msg-file-handle      PIC X(4).

status-code          See the section Key.

Description: 

This routine enables you to close a National Language Support
(NLS) message file that had been previously opened using the
CBL_NLS_OPEN_MSG_FILE routine.

Parameters on Entry: 

msg-file-handle      The identifying handle returned when the message
                     file was opened.

Parameters on Exit: 

status-code          Indicates whether the routine was successful:

                     0     = Success

                     40    = NLS module not initialized

                     404   = Invalid msg-file-handle

                           If status-code contains a value other than
                           these, it will the number of a run-time error
                           message.

CBL_NLS_COMPARE 

This routine is reserved for use on other environments; it has no effect
on UNIX. See Chapter 30  National Language Support for details on NLS
routines available on UNIX.

Syntax: 

     CALL "CBL_NLS_COMPARE" USING string1
                                  string2
                            BY VALUE string1-length
                            BY VALUE string2-length
                            BY REFERENCE result-byte
                            RETURNING status-code

Parameters: 

string1              PIC X(n).

string2              PIC X(n).

string1-length       PIC X(4) COMP-5.

string2-length       PIC X(4) COMP-5.

result-byte          PIC S9 COMP-X.

status-code          See the section Key.

Description: 

This routine compares two strings. 

Parameters on Entry: 

string1              The first string.

string2              The second string.

string1-length       Length of the first string.

string2-length       Length of the second string.

Parameters on Exit: 

result-byte          Result of the comparison:

                      0 = The two strings have equal weights
                     -1 = string1 < string2
                     +1 = string1 > string2

status-code          Indicates whether the routine was successful:

                     0  = Success
                     40 = NLS module not initialized

CBL_NLS_INFO 

This routine is reserved for use on other environments; it has no effect
on UNIX. See Chapter 30 , National Language Support for details on NLS
routines available on UNIX.

Syntax: 

     CALL "CBL_NLS_INFO" USING function-code
                               info-category
                               info-buffer
                         RETURNING status-code

Parameters: 

function-code        PIC X COMP-X.

info-category        PIC X COMP-X.

info-buffer          PIC X(n).

status-code          See the section Key.

Function-code        contains one of the following subfunction numbers:
                     1 = Get national language information
                     2 = Set national language information
                     3 = Reserved
                     4 = Reserved

Description: 

This routine allows you to both get and set information about the
national language.  With function-code = 2 (set information) the change
made will only apply to the program that made the call.

Parameters on Entry: 

info-category for    Category of information to get from the NLS module:
function-code = 1
                     1 = Currency symbol
                     2 = Thousands separator
                     3 = Decimal separator

for function-code =  Category of information to set:
2
                     1 = Currency symbol
                     2 = Thousands separator
                     3 = Decimal separator

info-buffer          Information to set - null-terminated (for
                     function-code=2).

Parameters on Exit: 

info-buffer          The information requested (for function-code = 1)

status-code

for function-code =  Indicates whether the routine was successful:
1
                     0 = Success
                     40 = NLS module not initialized

for function-code =  Indicates whether the routine was successful:
2
                     0 = Success
                     40 = NLS module not initialized
                     405 = Failure

CBL_NLS_OPEN_MSG_FILE 

This routine is reserved for use on other environments; it has no effect
on UNIX. See Chapter 30 , National Language Support for details on NLS
routines available on UNIX.

Syntax: 

     CALL "CBL_NLS_OPEN_MSG_FILE" USING msg-file-name
                                    msg-file-name-length
                                    msg-file-handle
                               RETURNING status-code

Parameters: 

msg-file-name        PIC X(n).

msg-file-name-       PIC X COMP-X.
length

msg-file-handle      PIC X(4).

status-code          See the section Key.

Description: 

This routine opens an NLS message file, returning an identifying handle
that you can use with the CBL_NLS_READ_MSG and CBL_NLS_CLOSE_MSG_FILE
routines.  You can create different message files for each language you
want your program to work with, using the same call to access each
message in the appropriate national language.  You can use a default
message file, or create your own.

Parameters on Entry: 

msg-file-name        The name of the message file to be opened.

msg-file-name-       The length of msg-file-name.  If this parameter is
length               set to zero, the default message file will be opened
                     regardless of the contents of msg-file-name.

Parameters on Exit: 

msg-file-handle      The identifying handle.

status-code          Indicates whether the routine was successful:

                     0 = Success
                     40 = NLS module not initialized

                     If status-code contains a value other than these, it
                     will be the number of a run-time error message.

CBL_NLS_READ_MSG 

This routine is reserved for use on other environments; it has no effect
on UNIX. See Chapter 30 , National Language Support for details on NLS
routines available on UNIX.

Syntax: 

     CALL "CBL_NLS_READ_MSG" USING msg-file-handle
                                   full-msg-number
                                   msg-insertion-structure
                                   msg-buffer
                             RETURNING status-code

Parameters: 

msg-file-handle            PIC X(4).

full-msg-number            Group item defined as:

  msg-set-number           PIC X(2) COMP-X.

  msg-number               PIC X(2) COMP-X.

msg-insertion-structure    Group item defined as:

  insertion-count          PIC X(2) COMP-X.

  insertion-pointer        USAGE POINTER OCCURS n TIMES.

msg-buffer                 Group item defined as:

  msg-buffer-length        PIC X(2) COMP-X.

  msg-buffer-text          PIC X(n).

status-code                See the section Key.

Description: 

Reads a message from a National Language Support (NLS) message file.

In each message file, messages are divided into sets; this enables you to
define your own message set in the default message file if you wish.
This routine also enables you to insert portions of text into a message
fetched from the message file in the order appropriate to the rules of
the grammar for the national language.

Parameters on Entry: 

msg-file-handle      The identifying handle of the message file to fetch
                     the message from.

msg-set-number       The set in the message file to fetch the message
                     from.

msg-number           The message number in the message set to fetch the
                     message from.

insertion-count      The number of portions of text to insert in to the
                     message.

insertion-pointer    A pointer to a null-terminated portion of text to
                     insert in to the message.

msg-buffer-length    The length of msg-buffer-text.

Parameters on Exit: 

msg-buffer-text      The returned text (null-terminated).

status-code          Indicates whether the routine was successful

                     0      = Success
                     40     = NLS module not initialized
                     401    = Message set not found
                     402    = Message not found in set
                     403    = Message too long for msg-text-buffer
                     404    = Invalid msg-file-handle

                     If status-code contains a value other than these, it
                     will be the number of a run-time error message.

CBL_NOT 

Does a logical NOT 
on the bits of a data item.

Syntax: 

     CALL "CBL_NOT" USING target
                    BY VALUE length
                    RETURNING status-code

Parameters: 

target               Any data item.

length               Numeric literal or PIC X(4) COMP-5.

status-code          See the section Key.

Description: 

The routine starts at the left-hand end of target and inverts bits.  The
truth table for this is:

before        after 

0             1

1             0

See also Logic Operators in the section "Routines by Category"  
earlier in this chapter.

Parameters on Entry: 

target               The data to operate on.

Parameters on Exit: 

target               The data with the bits inverted.

length               The number of bytes of target to change.  Positions
                     beyond this are unchanged.

CBL_OPEN_FILE 

Opens an existing file for byte-stream operations. 

Syntax: 

     CALL "CBL_OPEN_FILE" USING file-name
                                access-mode
                                deny-mode
                                path
                                file-handle
                          RETURNING status-code

Parameters: 

file-name            PIC X(n).

access-mode          PIC X COMP-X.

deny-mode            PIC X COMP-X.

path                 PIC X COMP-X.

file-handle          PIC X(4).

status-code          See the section Key.

Description: 

See Byte-stream Files in the section "Routines by Category"  earlier
in this chapter.

Parameters on Entry: 

file-name            Space- or null-terminated file-name of the file to
                     be opened.

access-mode          Defines access mode:

                     1 = read only
                     2 = write only (deny-mode must be 0)
                     3 = read/write

deny-mode            Defines deny mode:

                     0 = deny both read and write (exclusive)
                     1 = deny write
                     2 = deny read
                     3 = deny neither read nor write

path                 Reserved for future use (must be 0).

Parameters on Exit: 

file-handle          Returns a file handle for a successful open.

CBL_OPEN_VFILE 

Opens a heap. 

Syntax: 

     CALL "CBL_OPEN_VFILE" USING heap-id
                                 status-word

Parameters: 

heap-id              PIC X(2) COMP-5.

status-word          PIC X(2).

Description: 

See Virtual Heaps in the section "Routines by Category"  earlier in
this chapter.

Parameters on Entry: 

None

Parameters on Exit: 

heap-id              This contains the heap handle assigned.  A heap
                     handle of zero means the open failed.

status-word          The status word for the heap, set to zero on the
                     open.  When heap-id=9, binary values in second
                     status byte are:

                     000 = heap closed by user request
                     001 = heap access failure - out of buffers
                     002 = heap deallocated while programinactive
                     014 = backing-file failure:  too many files
                     037 = backing-file failure:  file access denied
                     201 = backing-file failure:  I/O failure

                     status-word remains associated with the heap until
                     the heap is closed; the first byte is set to ASCII
                     zero by a successful OPEN; status-word will be
                     written as file status data by a subsequent heap
                     READ or WRITE or CLOSE that encounters allocation or
                     I/O errors (but is not reset to zero by successful
                     operations).

                     If a program in which a heap status-word actually
                     exists (that is, it is not in a Linkage Section) is
                     canceled, all heaps with status-words in that
                     program are automatically canceled, and the heap
                     identifiers (which may have been passed to other
                     programs) should not be used any more.

CBL_OR 

Does a logical OR 
between the bits of two data items.

Syntax: 

     CALL "CBL_OR" USING source
                         target
                   BY VALUE length
                   RETURNING status-code

Parameters: 

source               Any data item.

target               Any data item.

length               Numeric literal or PIC X(4) COMP-5.

status-code          See the section Key.

Description: 

The routine starts at the left-hand end of source and target and ORs the
bits together, storing the result in target.  The truth table for this
is:

 source   target   result 

   0        0        0
   0        1        1
   1        0        1
   1        1        1

See also Logic Operators in the section "Routines by Category"  
earlier in this chapter.

Parameters on Entry: 

source               One of the data items to OR.

target               The other data item to OR.

length               The number of bytes of source and target to OR.
                     Positions in target beyond this are unchanged.

Parameters on Exit: 

target               The result.

CBL_PUT_SHMEM_PTR 

Creates or updates a named value. 

Syntax: 

     CALL "CBL_PUT_SHMEM_PTR" USING BY VALUE node-value
                          BY REFERENCE node-name
                          RETURNING status-code

Parameters: 

node-value           USAGE POINTER.

node-name            Group item defined as:

  name-length        PIC X COMP-5 VALUE n.

  name               PIC X(n) VALUE "name".

status-code          See the section Key.

Description: 

Named values provide a way of passing pointers between different
run-units using a name agreed at run-time.  Named values can be read
simultaneously by all units in the coru 
because the run-time system protects and serializes any updates.  The
maximum number of named values depends on how much memory your machine
has.

Parameters on Entry: 

node-value           The value to assign to the created/updated named
                     value.

name-length          The length of name.

name                 The name of the named value.

Parameters on Exit: 

None

CBL_READ_DIR 

Returns the current directory or path. 

Syntax: 

     CALL "CBL_READ_DIR" USING path-name
                               path-name-length
                         RETURNING status-code

Parameters: 

path-name            PIC X(n).

path-name-length     PIC X COMP-X.

status-code          See the section Key.

Parameters on Entry: 

path-name-length     Length of path-name to be used.  If this is too
                     small for the path-name, the routine fails.

Parameters on Exit: 

path-name            Relative or absolute path-name terminated by space
                     or null (x"00").

CBL_READ_FILE 

Reads bytes from a file. 

Syntax: 

     CALL "CBL_READ_FILE" USING file-handle
                                file-offset
                                byte-count
                                flags
                                buffer
                          RETURNING status-code

Parameters: 

file-handle          PIC X(4).

file-offset          PIC X(8) COMP-X.

byte-count           PIC X(4) COMP-X.

flags                PIC X COMP-X.

buffer               PIC X(n).

status-code          See the section Key.

Description: 

See also Byte-Stream Files in the section "Routines by Category"  
earlier in this chapter.

Parameters on Entry: 

file-handle          The file handle returned when the file was opened.

file-offset          The offset in file at which to read.  This field is
                     currently limited to a maximum value of
                     x"00FFFFFFFF".

byte-count           The number of bytes to read.  This field is
                     currently limited to a maximum value of x"00FFFF".

flags                This parameter can take the following values:

                     0 for standard read
                     128 to have the current file size returned in the
                     file-offset field

Parameters on Exit: 

file-offset          Contains the current file size on return if the
                     flags parameter is set to 128 on entry.

buffer               The buffer into which the bytes are read.  It is
                     your responsibility to ensure that the buffer is
                     large enough to hold the number of bytes to be read.
                     The buffer parameter is allowed to cross a 64K
                     segment boundary.

CBL_READ_KBD_CHAR 

Waits until a character is typed and then reads it with no echo. 

Syntax: 

     CALL "CBL_READ_KBD_CHAR" USING char
                              RETURNING status-code

Parameters: 

char                 PIC X.

status-code          See the section Key.

Parameters on Entry: 

None

Parameters on Exit: 

char                 The character that was typed, in ASCII.

CBL_READ_MOUSE_EVENT 

This routine is reserved for use on other environments; it has no effect
on UNIX.

Syntax: 

     CALL "CBL_READ_MOUSE_EVENT" USING mouse-handle
                                       event-data
                                       read-type
                                 RETURNING status-code

Parameters: 

mouse-handle         PIC X(4) COMP-X.

event-data           Group item defined as:

  event-type           PIC X(2) COMP-X

  event-time           PIC X(4) COMP-X

  event-row            PIC X(2) COMP-X

  event-col            PIC X(2) COMP-X

read-type              PIC X COMP-X.

status-code          See the section Key.

Description: 

This routine reads the mouse event queue and returns information about an
event. 

If there are no events in the event queue, the return from this routine
depends on the value of read-type.  If read-type is zero, the routine
returns immediately with all zero values in event-data.  If read-type has
a value of one, return is delayed until an event has been queued.

Parameters on Entry: 

mouse-handle         Mouse identifier, obtained by earlier call to
                     CBL_INIT_MOUSE.

read-type            Indicates what to do if there are no events in the
                     queue:

                     0 = return immediately
                     1 = wait for an event, then return.

Parameters on Exit: 

event-data           A description of the mouse event generated.

CBL_READ_SCR_ATTRS 

Reads a string of attributes from the screen. 

Syntax: 

     CALL "CBL_READ_SCR_ATTRS" USING screen-position
                                     attribute-buffer
                                     string-length
                               RETURNING status-code

Parameters: 

screen-position      Group item defined as:

  row-number         PIC X COMP-X.

  column-number      PIC X COMP-X.

attribute-buffer     PIC X(n).

string-length        PIC X(2) COMP-X.

status-code          See the section Key.

Parameters on Entry: 

screen-position      The screen position to start reading at.  The top
                     left corner is row 0, column 0.

string-length        The length of the string to read.

Parameters on Exit: 

attribute-buffer     The attributes read from the screen.  This data item
                     must be at least as long as specified by
                     string-length; positions in it beyond that length
                     are unchanged.

string-length        If the end of the screen is reached, the length read
                     is returned in here.

CBL_READ_SCR_CHARS 

Reads a string of characters from the screen. 

Syntax: 

     CALL "CBL_READ_SCR_CHARS" USING screen-position
                                     character-buffer
                                     string-length
                               RETURNING status-code

Parameters: 

screen-position      Group item defined as:

  row-number         PIC X COMP-X.

  column-number      PIC X COMP-X.

character-buffer     PIC X(n).

string-length        PIC X(2) COMP-X.

status-code          See the section Key.

Parameters on Entry: 

screen-position      The screen position to start reading at.  The top
                     left corner is row 0, column 0.

string-length        The length of the string to read.

Parameters on Exit: 

character-buffer     The characters read from the screen.  This data item
                     must be at least as long as specified by
                     string-length; positions in it beyond that length
                     are unchanged.

string-length        If the end of the screen is reached, the length read
                     is returned in here.

CBL_READ_SCR_CHATTRS 

Reads a string of characters and their attributes from the screen. 

Syntax: 

     CALL "CBL_READ_SCR_CHATTRS" USING screen-position
                                       character-buffer
                                       attribute-buffer
                                       string-length
                                 RETURNING status-code

Parameters: 

screen-position      Group item defined as:

  row-number         PIC X COMP-X.

  column-number      PIC X COMP-X.

character-buffer     PIC X(n).

attribute-buffer     PIC X(n).

string-length        PIC X(2) COMP-X.

status-code          See the section Key.

Parameters on Entry: 

screen-position      The screen position at which to start reading.  The
                     top left corner is row 0, column 0.

string-length        The length of the string to read.

Parameters on Exit: 

character-buffer     The characters read from the screen.  This data item
                     must be at least as long as specified by
                     string-length; positions in it beyond that length
                     are unchanged.

attribute-buffer     The attributes read from the screen.  This data item
                     must be at least as long as specified by
                     string-length; positions in it beyond that length
                     are unchanged.

string-length        If the end of the screen is reached, the length read
                     (in cells, that is, character- attribute pairs) is
                     returned in here.

CBL_READ_VFILE 

Reads bytes from a heap. 

Syntax: 

     CALL "CBL_READ_VFILE" USING BY VALUE heap-id
                                 heap-ref
                                 heap-len
                           BY REFERENCE heap-buf

Parameters: 

heap-id              PIC X(2) COMP-5.

heap-ref             PIC X(4) COMP-5.

heap-len             PIC X(4) COMP-5.

heap-buf             PIC X(n).

Description: 

See also Virtual Heaps in the section "Routines by Category"  earlier
in this chapter.

Warning: 

Attempting to read data from an area of the heap which has not yet been
written will result in indeterminate data being returned to the buffer.

Parameters on Entry: 

heap-id              This contains the heap handle assigned when the heap
                     was opened.

heap-ref             Offset in heap at which to start reading.

heap-len             Number of bytes to read.

Parameters on Exit: 

heap-buf             Buffer into which bytes are read.  It is your
                     responsibility to ensure that the buffer is large
                     enough to hold the number of bytes being read.

CBL_RENAME_FILE 

Changes the name 
of a file.

Syntax: 

     CALL "CBL_RENAME_FILE" USING old-file-name
                                  new-file-name
                            RETURNING status-code

Parameters: 

old-file-name        PIC X(n).

new-file-name        PIC X(n).

status-code          See the section Key.

Parameters on Entry: 

old-file-name        The file to rename.  The name can contain a
                     path-name, and is terminated by a space or a null.
                     If no path is given, the current directory is
                     assumed.

new-file-name        The new name, terminated by a space.  If
                     old-file-name contains a path-name, this must
                     contain the same path-name.  Note that some
                     operating systems do not allow you to rename a file
                     to new-file-name if a file of that name already
                     exists.

Parameters on Exit: 

None

CBL_SET_CSR_POS 

Moves the cursor. 

Syntax: 

     CALL "CBL_SET_CSR_POS" USING screen-position
                            RETURNING status-code

Parameters: 

screen-position      Group item defined as:

  row-number         PIC X COMP-X.

  column-number      PIC X COMP-X.

status-code          See the section Key.

Parameters on Entry: 

screen-position      The screen position at which to put the cursor.  The
                     top left corner is row 0, column 0.  Specifying
                     values greater than row-number or column-number
                     results in the cursor being displayed in the bottom
                     right corner of the screen.

Parameters on Exit: 

None



MPE/iX 5.0 Documentation