HP 3000 Manuals

Operation [ 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 

To use a library routine, use 
the name of the required routine in a COBOL CALL statement.

Descriptions of Routines 

Descriptions for all of the call-by-name routines appear alphabetically.

Key 

Each description contains the routine name and function and the entries
(as appropriate) noted below.

Syntax: 

Shows the CALL statement you could use to call the routine.  The
parameters you have to define are listed in the USING clause.

The optional RETURNING clause is also shown.  Every routine returns a
value showing the result of the operation.  Unless otherwise indicated,
zero indicates success, nonzero indicates failure.  This value is left in
the data item specified in the RETURNING clause - in this manual,
status-code. 
If this clause is omitted, the value is left in the special register
RETURN-CODE. Note that if call-convention bit two is set, RETURN-CODE
will not be changed.  See your Language Reference for details on
RETURN-CODE; the rules given there fo RETURN-CODE apply equally to
status-code.

Parameters: 

Describes any parameters shown in the RETURNING and USING clause.

Description: 

Provides any additional information necessary for the successful use of
the routine.

Parameters on Entry: 

Indicates which of the parameters shown are passed on entry.

Parameters on Exit: 

Indicates which of the parameters shown are returned on exit.

CBL_ALLOC_MEM 

Dynamically allocates memory at run time. 

Syntax: 

     CALL "CBL_ALLOC_MEM" USING mem-pointer
                       BY VALUE mem-size
                               flags

Parameters: 

mem-pointer               USAGE POINTER.
mem-size                  PIC X(4) COMP-5.
flags                     PIC X(4) COMP-5.

Description: 

This routine is used to allocate a block of memory which can then be
accessed by using the COBOL syntax:

set address of linkage-section-item to pointer

The program must ensure that it does not write past the end of any data
block allocated.  Any attempt to do so will not be detected, thus leading
to unpredictable behavior.

Non-shared memory is owned by the program that created it, and is
released when the program is canceled if it has not previously explicitly
been released using the CBL_FREE_MEM routine.  Shared memory is owned by
the coru; 
it is released when the coru is terminated.  See the description of
CBL_EXEC_RUN_UNIT for the definition of a coru.

Updates to any shared memory allocated to this function are not
serialized or protected by the run-time system; you should use semaphores
to maintain the integrity of the data.

The pointer returned by this routine is the pointer that you should pass
when you call CBL_PUT_SHMEM_PTR.

Parameters on Entry: 

memsize                   The number of bytes of memory to allocate.

flags                     Indicates the type of memory to allocate
                          according to the following bit settings:

                          bits 7 thru 2 reserved

                          bit 1 =  if the allocated memory is to be
                          0        relocatable.  This is the usual
                                   setting.

                          = 1      if the allocated memory is fixed.
                                   This bit has no effect on UNIX or
                                   OS/2.

                          bit 0 =  if memory is to be nonshared.  This is
                          0        the usual setting.

                          = 1      if memory is to be shared between
                                   run-units.

Parameters on Exit: 

mem-pointer         A pointer to the memory returned.  mem-pointer must
                    be a 01-level data item.

CBL_AND 

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

Syntax: 

     CALL "CBL_AND" 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 ANDs the
bits together, storing the result in target.  The truth table for this
is:

 source   target   result 

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

Parameters on Entry: 

source   One of the data items to AND.

target   The other data item to AND.

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

Parameters on Exit: 

target   The result.

CBL_CHANGE_DIR 

Changes the current directory. 

Syntax: 

     CALL "CBL_CHANGE_DIR" USING path-name
                           RETURNING status-code

Parameters: 

path-name             PIC X(n).

status-code           See the section Key.

Parameters on Entry: 

path-name             Relative or absolute path-name terminated by space
                      or null (x"00").  This must be no longer than the
                      number of characters allowed by your operating
                      system and must be valid from the directory that is
                      current when the routine is called.

Parameters on Exit: 

None

CBL_CHECK_FILE_EXIST 

Checks whether a file exists and returns details if it does. 

Syntax: 

     CALL "CBL_CHECK_FILE_EXIST" USING file-name
                                       file-details
                                 RETURNING status-code

Parameters: 

file-name                          PIC X(n).
file-details                       Group item defined as:
  file-size                           PIC X(8) COMP-X.
  file-date                           PIC X COMP-X.
    day                               PIC X COMP-X.
    month                             PIC X(2) COMP-X.
    year                            
  file-time                           PIC X COMP-X.
    hours                             PIC X COMP-X.
    minutes                           PIC X COMP-X.
    seconds                           PIC X COMP-X.
    hundredths                     See the section Key.
status-code

Parameters on Entry: 

file-name            The file to look for.  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.

Parameters on Exit: 

file-size            The size of the file in bytes.

file-date            The date the file was created.

file-time            The time the file was created.

CBL_CLEAR_SCR 

Clears the whole screen to a specified character and attribute. 

Syntax: 

     CALL "CBL_CLEAR_SCR" USING character
                                attribute
                          RETURNING status-code

Parameters: 

character            PIC X.

attribute            PIC X.

status-code          See the section Key.

Parameters on Entry: 

character            The character to write.

attribute            The attribute to write.  See the appendix Generic 
                     Attributes for details on attributes.

Parameters on Exit: 

None

CBL_CLOSE_FILE 

Closes a file opened for byte-stream operations. 

Syntax: 

     CALL "CBL_CLOSE_FILE" USING file-handle
                           RETURNING status-code

Parameters: 

file-handle          PIC X(4).

status-code          See the section Key.

Description: 

Any byte-stream file open when a STOP RUN is executed is automatically
closed.

Parameters on Entry: 

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

Parameters on Exit: 

None

CBL_CLOSE_VFILE 

Closes a heap. 

Syntax: 

     CALL "CBL_CLOSE_VFILE" USING BY VALUE heap-id

Parameters: 

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

Parameters on Entry: 

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

Parameters on Exit: 

None

CBL_COPY_FILE 

Copies a file. 

Syntax: 

     CALL "CBL_COPY_FILE" USING file-name1
                                file-name2
                          RETURNING status-code

Parameters: 

file-name1           PIC X(n).

file-name2           PIC X(n).

status-code          See the section Key.

Parameters on Entry: 

file-name1           The file to copy.  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.

file-name2           The name of the new file.  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.

Parameters on Exit: 

None

CBL_CREATE_DIR 

Creates a subdirectory. 
All the directories in the given path, except the last, must already
exist.

Syntax: 

     CALL "CBL_CREATE_DIR" USING path-name
                           RETURNING status-code

Parameters: 

path-name            PIC X(n).

status-code          See the section Key.

Parameters on Entry: 

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

Parameters on Exit: 

None

CBL_CREATE_FILE 

Creates a new file for byte-stream operations. 

Syntax: 

     CALL "CBL_CREATE_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.

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_CULL_RUN_UNITS 

Clears any dead run-units. 

Syntax: 

     CALL "CBL_CULL_RUN_UNITS"

Parameters: 

None

Description: 

CBL_CULL_RUN_UNITS clears any run-units that have been terminated by a
STOP RUN or Kill, but have not yet been removed.  This routine sets
RETURN-CODE to zero for success, nonzero for failure.

Parameters on Entry: 

None

Parameters on Exit: 

None

CBL_DELETE_DIR 

Deletes a directory. 
A directory will only be deleted if it is empty.

Syntax: 

     CALL "CBL_DELETE_DIR" USING path-name
                           RETURNING status-code

Parameters: 

path-name            PIC X(n).

status-code          See the section Key.

Parameters on Entry: 

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

Parameters on Exit: 

None

CBL_DELETE_FILE 

Deletes a file. 

Syntax: 

     CALL "CBL_DELETE_FILE" USING file-name
                            RETURNING status-code

Parameters: 

file-name            PIC X(n).

status-code          See the section Key.

Parameters on Entry: 

file-name            The file to delete.  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.

Parameters on Exit: 

None

CBL_EQ 

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

Syntax: 

     CALL "CBL_EQ" 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
EQUIVALENCEs the bits together, storing the result in target.  The truth
table for this is:

 source   target   result 

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

Parameters on Entry: 

source               One of the data items to EQUIVALENCE.

target               The other data item to EQUIVALENCE.

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

Parameters on Exit: 

target               The result.

CBL_ERROR_PROC 

Posts and removes user error procedures.

Syntax: 

     CALL "CBL_ERROR_PROC" USING install-flag
                                 install-address
                           RETURNING status-code

Parameters: 

install-flag         PIC X COMP-X.

install-address      USAGE PROCEDURE POINTER

status-code          See the section Key.

Description: 

The routine sets RETURN-CODE to zero for success, nonzero for failure.
You can post several error procedures for an application by repeated
calls of this routine.

An error procedure can be written in any language.  If it is in COBOL,
install-address must be the address of an entry point.  You can obtain
this address using the statement:  set install-address to entry
entry-name

An error procedure in COBOL can include any legal COBOL, including CALL
statements.

Parameters on Entry: 

install-flag         Indicates the operation to be performed:

                     0 = install error procedure
                     1 = de-install error procedure

install-address      Address of error procedure.

Parameters on Exit: 

None

CBL_EXEC_RUN_UNIT 

Creates an asynchronous run-unit. 

Syntax: 

     CALL "CBL_EXEC_RUN_UNIT" USING command-line
                           BY VALUE command-line-length
                           BY REFERENCE run-unit-id
                           BY VALUE stack-size
                                    flags

Parameters: 

command-line         PIC X(n).

command-line-length  PIC X(4) COMP-5.

run-unit-id          PIC X(8) COMP-5.

stack-size           PIC X(4) COMP-5.

flags                PIC X(4) COMP-5.

Description: 

The run-unit that makes the call is known as the parent, while the
run-unit created is known as the child.  On creation, the child inherits
certain attributes from its parent.  The attributes inherited by the
child are copies of the attributes in the parent at the exact time of the
call; any changes made to the attributes of the parent after the call are
not reflected in the child's attributes.  Similarly, any changes made to
the child's attributes are not reflected in the parent's attributes.

The set of run-units containing the initial run-unit and all run-units
created from it is known as the coru. 

You should be aware of the following when using run-units:

   *   All COBOL programs in the child are in their initial state.

   *   To improve both speed and size, the stack-size and flags
       parameters should be either literal or level-01 items.

   *   Data is not shared between run-units unless explicitly specified
       using the CBL_GET_SHMEM_PTR or CBL_ALLOC_MEM routine.

   *   COBOL and RTS switches, environment variables, and open libraries
       are inherited by the child.

   *   Open files and heaps are not inherited by the child.

After using CBL_EXEC_RUN_UNIT, RETURN-CODE will contain one of the
following values:

       0 = Success
     157 = Out of memory
     181 = Invalid parameter
     200 = Internal logic error

Parameters on Entry: 

command-line         The command passed to the new run-unit.  This should
                     be the program name followed by any parameters.  For
                     example:

                          check a.cbl nolist nocheck
                                               nooptional-file

command-line-length  The length of the command-line.

stack-size           Suggests the size of the stack (in bytes) to be
                     allocated to the new run-unit.  Specifying zero for
                     this parameter causes the child's stack to be the
                     same size as the parent's.  This parameter is
                     ignored if running under UNIX.

flags                Reserved for future use.  Must be zero.

Parameters on Exit: 

run-unit-id          The unique handle identifying the new run-unit.
                     This must be a 01-level data item.

CBL_EXIT_PROC 

Posts or removes a closedown procedure to be invoked automatically when
the application terminates. 

Syntax: 

     CALL "CBL_EXIT_PROC" USING install-flag
                                install-address
                          RETURNING status-code

Parameters: 

install-flag         PIC X COMP-X.

install-address      USAGE PROCEDURE POINTER

status-code          See the section Key.

Description: 

The routine sets RETURN-CODE to zero for success, nonzero for failure.
The procedure will be executed whether the application finishes normally
(with a STOP RUN) or abnormally (with a keyboard interrupt, RTS error,
etc).  You can install several closedown procedures for an application by
repeated calls of this routine.

A closedown procedure can be written in any language.  If it is in COBOL,
install-address must be the address of an entry point.  You can obtain
this address using the statement:

set install-address to entry entry-name

A closedown procedure in COBOL can include any legal COBOL, including
CALL statements.  The closedown procedure will terminate when the main
program in the procedure does a GOBACK or when a STOP RUN statement is
executed.

Parameters on Entry: 

install-flag         Indicates the operation to be performed:

                     0 = install closedown procedure
                     1 = de-install closedown procedure

install-address      Address of closedown procedure.

Parameters on Exit: 

None

CBL_FREE_MEM 

Frees dynamically allocated memory. 

Syntax: 

     CALL "CBL_FREE_MEM" USING BY VALUE mem-pointer
                      RETURNING status-code

Parameters: 

mem-pointer          USAGE POINTER.

status-code          See the section Key.

Parameters on Entry: 

mem-pointer          The pointer returned when the memory was allocated
                     using CBL_ALLOC_MEM.

Parameters on Exit: 

None

CBL_GET_CSR_POS 

Returns the cursor position. 

Syntax: 

     CALL "CBL_GET_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: 

None

Parameters on Exit: 

screen-position      The screen position of the cursor.  The top left
                     corner is row 0, column 0.  If the cursor is
                     invisible, row-number and column-number are both set
                     to 255.

CBL_GET_KBD_STATUS 

Checks whether there is a character waiting to be read from the keyboard. 

Syntax: 

     CALL "CBL_GET_KBD_STATUS" USING key-status
                               RETURNING status-code

Parameters: 

key-status           PIC X COMP-X.

status-code          See the section Key.

Parameters on Entry: 

None

Parameters on Exit: 

key-status           0 = no character available
                     1 = character available

CBL_GET_MOUSE_MASK 

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

Syntax: 

     CALL "CBL_GET_MOUSE_MASK" USING mouse-handle
                                     event-mask
                               RETURNING status-code

Parameters: 

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

event-mask           PIC X(2) COMP-X.

status-code          See the section Key.

Description: 

Returns the mouse event mask.

Parameters on Entry: 

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

Parameters on Exit: 

event-mask           User-supplied item which tells the system which
                     kinds of event should be queued and which ignored.

CBL_GET_MOUSE_POSITION 

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

Syntax: 

     CALL "CBL_GET_MOUSE_POSITION" USING mouse-handle
                                         mouse-position
                                   RETURNING status-code

Parameters: 

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

mouse-position       Group item defined as:

  mouse-row          PIC X(2) COMP-X.

  mouse-col          PIC X(2) COMP-X.

status-code          See the section Key.

Description: 

Returns the screen position of the mouse pointer. 

Parameters on Entry: 

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

Parameters on Exit: 

mouse-position       The screen position of the mouse pointer.

CBL_GET_MOUSE_STATUS 

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

Syntax: 

     CALL "CBL_GET_MOUSE_STATUS" USING mouse-handle
                                       queued-events
                                 RETURNING status-code

Parameters: 

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

queued-events        PIC X(2) COMP-X.

status-code          See the section Key.

Description: 

Finds out the number of events in the mouse event queue. 

Parameters on Entry: 

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

Parameters on Exit: 

queued-events        The number of events in the queue.

CBL_GET_OS_INFO 

Returns information about the operating system environment. 

Syntax: 

     CALL "CBL_GET_OS_INFO" USING parameter-block
                            RETURNING status-code

Parameters: 

parameter-block      Group item defined as:

  parameter-size     PIC X(2) COMP-X VALUE 14.

  p-os-type          PIC X COMP-X.

  p-os-version       PIC X(4) COMP-X.

  p-DBCS-support     PIC X COMP-X.

  p-char-coding      PIC X COMP-X.

  p-country-id       PIC X(2) COMP-X.

  p-code-page        PIC X(2) COMP-X.

  p-process-type     PIC X COMP-X.

status-code          See the section Key.

Parameters on Entry: 

None

Parameters on Exit: 

p-os-type              0       = OS/2

                     1       = DOS
                     2       = DOS + XM
                     4       = FLEXOS
                     5       = MS-Windows
                     128     = UNIX
                     129     = XENIX

p-os-version         Use is specific to the operating system.  May
                     include information such as chip type and the
                     operating system version number.  For DOS and OS/2,
                     the third and fourth bytes contain the minor and
                     major release operating system version number
                     respectively.

p-DBCS-support         Bit 0    = 0 if DBCS validation unsupported
                              = 1 if DBCS validation supported

                     Bit 1    = 0 if PIC N data type unsupported
                              = 1 if PIC N data type supported

p-char-coding        0 = ASCII
                     1 = Shift-JIS
                     2 = EUC

p-country-id         Currently unsupported.  Returns zero.

p-code-page          Currently unsupported.  Returns zero.

p-process-type       Currently unsupported.  Not set by this routine.

CBL_GET_SCR_SIZE 

Returns information on the size of the screen. 

Syntax: 

     CALL "CBL_GET_SCR_SIZE" USING depth
                                   width
                             RETURNING status-code

Parameters: 

depth                PIC X COMP-X.

width                PIC X COMP-X.

status-code          See the section Key.

Parameters on Entry: 

None

Parameters on Exit: 

depth                Number of lines.

width                Number of columns.

CBL_GET_SHMEM_PTR 

Reads a named value. 

Syntax: 

     CALL "CBL_GET_SHMEM_PTR" USING node-value
                               node-name

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".

Parameters on Entry: 

name-length          The length of name.

name                 The name of the queried named value.

Parameters on Exit: 

node-value           The value assigned to node-name.

CBL_HIDE_MOUSE 

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

Syntax: 

     CALL "CBL_HIDE_MOUSE" USING mouse-handle
                           RETURNING status-code

Parameters: 

mouse-handle         PIC X(4) COMP-X

status-code          See the section Key.

Description: 

Makes the mouse pointer invisible. 
After this routine has been called, mouse events still take place, but
the mouse pointer is not displayed.

Parameters on Entry: 

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

Parameters on Exit: 

None

CBL_IMP 

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

Syntax: 

     CALL "CBL_IMP" 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 IMPLIES
the bits together, storing the result in target.  The truth table for
this is:

 source   target   result 

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

Parameters on Entry: 

source               One of the data items to IMPLIES.

target               The other data item to IMPLIES.

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

Parameters on Exit: 

target               The result.

CBL_INIT_MOUSE 

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

Syntax: 

     CALL "CBL_INIT_MOUSE" USING mouse-handle
                                 mouse-buttons
                           RETURNING status-code

Parameters: 

mouse-handle         PIC X(4) COMP-X

mouse-buttons        PIC X(2) COMP-X

status-code          See the section Key.

Description: 

Initializes mouse support.  This routine must be called before other
mouse routines can be called. 

Parameters on Entry: 

None

Parameters on Exit: 

mouse-handle         Mouse identifier.  You pass this to any mouse
                     routines you call subsequently.

mouse-buttons        The number of buttons on the mouse.



MPE/iX 5.0 Documentation