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_SET_MOUSE_MASK 

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

Syntax: 

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

Sets the mouse event mask. 
CBL_GET_MOUSE_MASK should be called first to find out which events are
enabled.

Parameters on Entry: 

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

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

Parameters on Exit: 

None

CBL_SET_MOUSE_POSITION 

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

Syntax: 

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

This routine moves the mouse pointer. 

Parameters on Entry: 

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

mouse-position       The screen position to move the mouse pointer to.

Parameters on Exit: 

None

CBL_SHOW_MOUSE 

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

Syntax: 

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

Parameters: 

mouse-handle         PIC X(4) COMP-X

status-code          See the section Key.

Description: 

This routine makes the mouse pointer visible. 
When the mouse support has been initialized by the CBL_INIT_MOUSE call,
the pointer is not displayed until this routine is called.  After this
call the system displays the mouse pointer until a routine to hide the
mouse or terminate mouse support is called.

Parameters on Entry: 

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

Parameters on Exit: 

None

CBL_SPLIT_FILENAME 

Splits a file-name into its component parts; that is, the path-name,
base-name and extension. 

Syntax: 

     CALL "CBL_SPLIT_FILENAME" USING split-join-params
                                     split-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.

                              PI C X(2) COMP-X.
first-path-component-length

split-buffer                  PIC X(n).

status-code                   See the section Key.

Description: 

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.

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.

If there are two or more dots in the file-name (not counting dots in the
path-name), the extension returned consists of the characters between the
last dot and the end of the file-name.  The base-name contains everything
up to, but not including, the last dot.

To make a distinction between file-names with no extension and file-names
with spaces extension (that is, base-names whose last character is
a dot), if the extension is spaces extension-length is 1 and
extension-offset points to the last dot.

See also File-names in the section "Routines by Category"  earlier in
this chapter and the description for CBL_JOIN_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, specifies that the file-name is
                     null-terminated, otherwise it is space-terminated.
                     bit 0 - if set, specifies that the new strings will
                     be folded to upper case, otherwise the original case
                     will be preserved.  We recommend that you do not set
                     this flag if you intend to run your program on UNIX.

split-buf-len        Length of split-buffer.

split-buffer         The string to split.

Parameters on Exit: 

split-join-flag2     bit 1 - set if there is a wildcard in the path.
                     bit 0 - set if there is a wildcard in base-name or
                     extension.

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

path-length          Length of path-name; zero if there is none.  This
                     includes any following colon.

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

basename-length      Length of base-name; zero if there is none.  This
                     does not include the following dot.

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

extension-length     Length of extension; zero if there is none.  This
                     does not include the preceding dot.

total-length         Total number of characters in the string.

first-path-component-length

                     Number of characters up to and including the first
                     /; if split-buffer contains none of these, this
                     field = path-length.

split-buffer         Unchanged unless bit 1 of split-join-flag1 is set,
                     when it is folded to upper case.

status-code          0 = success
                     4 = illegal file-name

CBL_SUBSYSTEM 

Declares or deallocates subsystems. 

Syntax: 

     CALL "CBL_SUBSYSTEM" USING function-code
                                parameter
                          RETURNING status-code

Parameters: 

function-code        PIC X COMP-X.

                     Contains one of the following subfunction numbers:
                     0 = declare subsystem
                     1 = cancel subsystem
                     2 = remove from subsystem

parameter

for function-code =  Group item defined as:
0

    ss-handle        PIC X(2) COMP-X.

    ss-name-len      PIC X(2) COMP-X.

    ss-name          PIC X(n).

for function-code =
1
    ss-handle        PIC X(2) COMP-X.

for function-code =
2
    dummy-parameter  PIC X(2) COMP-X VALUE 0.

status-code          See the section Key.

Description: 

A subsystem is defined to be a specified program within an application,
plus any subprograms subsequently called by programs already in the
subsystem that do not already belong to any other subsystems.

With function-code = 0

This function declares a subsystem.  The routine returns a subsystem
handle.  If the program is not already loaded the function loads it.  If
an error occurs in finding or loading the program a subsystem handle of
zero is returned.  A program belonging to a subsystem will only be
deallocated (that is, deleted from memory), when either it is canceled by
the CANCEL verb, or the program cancels the entire subsystem using
function-code= 1, or the application executes a STOP RUN or CHAIN
statement.  The main program of a subsystem should not be canceled with
the CANCEL statement unless all other programs in the subsystem have
already been canceled.

With function-code = 1

This function cancels all programs in the specified subsystem.  If any
program in the subsystem is still active, that program is released from
the subsystem and is not canceled.

With function-code = 2

This function removes the program that called it from any subsystem the
program is in.  To ensure a program is never included in any subsystem,
call this function at the start of each entry in to the program.

Parameters on Entry: 

function-code        The subfunction number.

ss-name-len          The length of subsystem program-name field (for
                     function-code = 0)

ss-name              The subsystem program-name - space-terminated (for
                     function-code = 0).

ss-handle            The subsystem handle returned by a function 0 call
                     (for function-code = 1 ).

dummy parameter      Value 0 (for function-code = 2).

Parameters on Exit: 

ss-handle            The subsystem handle
                     (for function-code = 0)

CBL_SWAP_SCR_CHATTRS 

Swaps a string of characters and their attributes with a string from the
screen. 

Syntax: 

     CALL "CBL_SWAP_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 writing.  The
                     top left corner is row 0, column 0.

character-buffer     The characters to write.

attribute-buffer     The attributes to write.

string-length        The length of the string to write.  If this would go
                     off the end of the screen, the write finishes at the
                     end of the screen.

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
                     swapped (in cells, that is, character-attribute
                     pairs) is returned in here.

CBL_TERM_MOUSE 

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

Syntax: 

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

Parameters: 

mouse-handle         PIC X(4) COMP-X

status-code          See the section Key.

Description: 

The routine releases internal resources allocated by CBL_INIT_MOUSE.
After this routine, mouse-handle is no longer valid and calling any mouse
routine other than CBL_INIT_MOUSE will result in an error.

Parameters on Entry: 

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

Parameters on Exit: 

None

CBL_TOLOWER 

Converts a string of letters to lower case. 

Syntax: 

     CALL "CBL_TOLOWER" USING string
                        BY VALUE length
                        RETURNING status-code

Parameters: 

string               PIC X(n).

length               PIC X(4) COMP-5.

status-code          See the section Key.

Description: 

The routine starts at the left-hand end of string and converts letters to
lower case (also called folding to lower case).

Parameters on Entry: 

string               The string to convert.

length               The number of bytes of string to change; positions
                     beyond this are unchanged.

Parameters on Exit: 

string               The converted string.

CBL_TOUPPER 

Converts a string of letters to upper case. 

Syntax: 

     CALL "CBL_TOUPPER" USING string
                        BY VALUE length
                        RETURNING status-code

Parameters: 

string               PIC X(n).

length               PIC X(4) COMP-5.

status-code          See the section Key.

Description: 

The routine starts at the left-hand end of string and converts letters to
upper case (also called folding to upper case).

Parameters on Entry: 

string               The string to convert.

length               The number of bytes of string to change; positions
                     beyond this are unchanged.

Parameters on Exit: 

string               The converted string.

CBL_WRITE_FILE 

Writes bytes to a file. 

Syntax: 

     CALL "CBL_WRITE_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 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 write.  This field is
                     currently limited to a maximum value of
                     x"00FFFFFFFF".

byte-count           The number of bytes to write.  This field is
                     currently limited to a maximum value of x"00FFFF".
                     Putting a value of zero in this field will cause the
                     file to be truncated or extended to the size
                     specified in the file-offset field.

flags                This parameter can take the following value:
                     0 for standard write

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

Parameters on Exit: 

None

CBL_WRITE_SCR_ATTRS 

Writes a string of attributes to the screen. 

Syntax: 

     CALL "CBL_WRITE_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 at which to start writing.  The
                     top left corner is row 0, column 0.

attribute-buffer     The attributes to write.

string-length        The length of the string to write.  If this would go
                     off the end of the screen, the write finishes at the
                     end of the screen.

Parameters on Exit: 

None

CBL_WRITE_SCR_CHARS 

Writes a string of characters to the screen. 

Syntax: 

     CALL "CBL_WRITE_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 at which to start writing.  The
                     top left corner is row 0, column 0.

character-buffer     The characters to write.

string-length        The length of the string to write.  If this would go
                     off the end of the screen, the write finishes at the
                     end of the screen.

Parameters on Exit: 

None

CBL_WRITE_SCR_CHARS_ATTR 

Writes a string of characters to the screen, giving them all the same
attribute. 

Syntax: 

     CALL "CBL_WRITE_SCR_CHARS_ATTR" USING  screen-position
                                   character-buffer
                                   string-length
                                   attribute
                                 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            PIC X.

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 writing.  The
                     top left corner is row 0, column 0.

character-buffer     The characters to write.

attribute            The attribute to write.

string-length        The length of the string to write.  If this would go
                     off the end of the screen, the write finishes at the
                     end of the screen.

Parameters on Exit: 

None

CBL_WRITE_SCR_CHATTRS 

Writes a string of characters and their attributes to the screen. 

Syntax: 

     CALL "CBL_WRITE_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 writing.  The
                     top left corner is row 0, column 0.

character-buffer     The characters to write.

attribute-buffer     The attributes to write.

string-length        The length of the string to write.  If this would go
                     off the end of the screen, the write finishes at the
                     end of the screen.

Parameters on Exit: 

None

CBL_WRITE_SCR_N_ATTR 

Writes a specified attribute to a string of positions on the screen. 

Syntax: 

     CALL "CBL_WRITE_SCR_N_ATTR" USING screen-position
                                       attribute
                                       fill-length
                                 RETURNING status-code

Parameters: 

screen-position      Group item defined as:

  row-number         PIC X COMP-X.

  column-number      PIC X COMP-X.

attribute            PIC X.

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

status-code          See the section Key.

Parameters on Entry: 

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

attribute            The attribute to write.

string-length        The number of screen positions to write the
                     attribute to.  If this would go off the end of the
                     screen, the write finishes at the end of the screen.

Parameters on Exit: 

None

CBL_WRITE_SCR_N_CHAR 

Writes a specified character to a string of positions on the screen. 

Syntax: 

     CALL "CBL_WRITE_SCR_N_CHAR" USING screen-position
                                       character
                                       fill-length
                                 RETURNING status-code

Parameters: 

screen-position      Group item defined as:

  row-number         PIC X COMP-X.

  column-number      PIC X COMP-X.

character            PIC X.

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

status-code          See the section Key.

Parameters on Entry: 

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

character            The character to write.

string-length        The number of screen positions to write the
                     character to.  If this would go off the end of the
                     screen, the write finishes at the end of the screen.

Parameters on Exit: 

None

CBL_WRITE_SCR_N_CHATTR 

Writes a specified character and attribute to a string of positions on
the screen. 

Syntax: 

     CALL "CBL_WRITE_SCR_N_CHATTR" USING screen-position
                                         character
                                         attribute
                                         fill-length
                                   RETURNING status-code

Parameters: 

screen-position      Group item defined as:

  row-number         PIC X COMP-X.

  column-number      PIC X COMP-X.

character            PIC X.

attribute            PIC X.

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

status-code          See the section Key.

Parameters on Entry: 

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

character            The character to write.

attribute            The attribute to write.

string-length        The number of screen positions to write the
                     character-attribute pair to.  If this would go off
                     the end of the screen, the write finishes at the end
                     of the screen.

Parameters on Exit: 

None

CBL_WRITE_SCR_TTY 

Writes a string of characters to the screen starting at the current
position and scrolling. 

Syntax: 

     CALL "CBL_WRITE_SCR_TTY" USING character-buffer
                                    string-length
                              RETURNING status-code

Parameters: 

character-buffer     PIC X(n).

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

status-code          See the section Key.

Parameters on Entry: 

character-buffer     The characters to write.

string-length        The length of the string to write.  If this goes off
                     the edge of the screen the screen is scrolled up a
                     line and the write continues on the bottom line.

Parameters on Exit: 

None

CBL_WRITE_VFILE 

Writes bytes to a heap. 

Syntax: 

     CALL "CBL_WRITE_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 Virtual Heaps in the section "Routines by Category"  earlier in
this chapter.

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

heap-len             Number of bytes to write.

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

Parameters on Exit: 

None

CBL_XOR 

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

Syntax: 

     CALL "CBL_XOR" 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
exclusive-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        0

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

Parameters on Entry: 

source               One of the data items to exclusive-OR.

target               The other data item to exclusive-OR.

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

Parameters on Exit: 

target               The result.

CBL_YIELD_RUN_UNIT 

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

Syntax: 

     CALL "CBL_YIELD_RUN_UNIT"

Parameters: 

None

Description: 

The remainder of the run-unit's time-slice is yielded to unspecified
run-units.  This routine sets RETURN-CODE to zero for success, nonzero
for failure.

Parameters on Entry: 

None

Parameters on Exit: 

None



MPE/iX 5.0 Documentation