HP 3000 Manuals

List of Routines (cont.) [ Micro Focus COBOL System Reference, Volume 1 ] MPE/iX 5.0 Documentation


Micro Focus COBOL System Reference, Volume 1

List of Routines (cont.) 

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 section Key 

Remarks:.   

This routine releases memory allocated by the CBL_ALLOC_MEM routine.

On Entry:.   

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

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 section Key 

On Entry:.   

None

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.  See Notes on Screen Routines.

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 section Key 

On Entry:.   

None

On Exit:.   

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

CBL_GET_MOUSE_ MASK 

Returns the mouse event mask.

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 section Key 

Remarks:.   

This routine has no effect in UNIX environments.

See Introduction to Mouse Routines  

On Entry:.   

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

On Exit:.   

 event-mask         See Introduction to Mouse Routines

CBL_GET_MOUSE_ POSITION 

Returns the screen position of the mouse pointer.

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 section Key 

Remarks:.   

This routine has no effect in UNIX environments.

See Introduction to Mouse Routines  

On Entry:.   

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

On Exit:.   

 mouse-position     The screen position of the mouse pointer.

CBL_GET_MOUSE_ STATUS 

Finds out the number of events in the queue.

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 section Key 

Remarks:.   

This routine has no effect in UNIX environments.

See Introduction to Mouse Routines  

On Entry:.   

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

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 section Key 

On Entry:.   

None

On Exit:.   

 p-os-type          0 = OS/2
                    1 = DOS
                    2 = DOS + XM
                    4 = FLEXOS
                    5 = MS-Windows
                    128 = UNIX
                    129 = XENIX
                    130 = OS/2 - 32-bit
                    131 = Windows/NT

 p-os-version       Use is specific to the operating system.  Can 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       Country Code.  Zero is returned if the program was
                    not compiled with the NLS Compiler directive.  See
                    your operating system documentation for an
                    explanation of country codes.

                    Not supported in UNIX enviromnents - set to zero.

 p-code-page        Code Page.  Zero is returned if the program was not
                    compiled with the NLS Compiler directive.

                    Not supported in UNIX enviromnents - set to zero.

 p-process-type     0 = process is running in a full screen session
                    1 = process is running in a compatibility box
                    2 = process is running in a graphical
                    character-screen emulation
                    window
                    3 = process is running as a true graphical
                    application
                    4 = process is detached
                    5 = process is non-interactive (that is, no screen or
                    keyboard I/O)
                    and detached

                    Not supported in UNIX enviromnents - undefined.

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 section Key 

On Entry:.   

None

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

Remarks:.   

On DOS, Windows and OS/2 this routine is available only with the add-on
product, Toolset, available from Micro Focus.  It works only with .int
and .gnt files.  It does not work with linked object code.

On Entry:.   

 node-name          The length of name.

 name               The value assigned to node-name.

On Exit:.   

 node-value         The value of the named value.

CBL_HIDE_MOUSE 

Makes the mouse pointer invisible.

Syntax:.   

      call "CBL_HIDE_MOUSE"  using     mouse-handle
            returning status-code

Parameters:.   

 mouse-handle       PIC X(4) COMP-X
status-code         See section Key 

Remarks:.   

This routine has no effect in UNIX environments.

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

See Introduction to Mouse Routines.

On Entry:.   

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

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 section Key 

Remarks:.   

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

See Introduction to Logic Routines.

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.

On Exit:.   

 target             The result.

CBL_INIT_MOUSE 

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

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 section Key 

Remarks:.   

If status-code (or RETURN-CODE) contains a non-zero status on return from
this routine, then mouse handling is not available and calls to any of
the mouse routines should not be made.

In UNIX environments this routine always returns a non-zero status-code.

See Introduction to Mouse Routines  

On Entry:.   

None

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.

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-param
        join-buffer
        path-buffer
        basename-buffer
        extension-buffer
      returning status-code

Parameters:.   

 split-join-param   Group item defined as:
  param-length      PIC X(2) COMP-X.
  splitjoin-flg1    PIC X COMP-X.
  splitjoin-flg2    PIC X COMP-X.
  path-strt         PIC X(2) COMP-X
  path-len          PIC X(2) COMP-X.
  basename-strt     PIC X(2) COMP-X.
  basename-len      PIC X(2) COMP-X.
  extension-strt    PIC X(2) COMP-X.
  extension-len     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-len    PIC X(2) COMP-X.
 join-buffer        PIC X(n).
path-buffer         PIC X(n).
basename-buffer     PIC X(n).
extension-buffer    PIC X(n).
status-code         See section Key 

Remarks:.   

The new file-name is formed by concatenating:

   *   the first path-len bytes (starting from path-strt) of path-buffer

   *   the first basename-len bytes (starting from basename-strt) of
       basename-buffer

   *   the first extension-len bytes (starting from extension-strt) 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 splitjoin-flg1.  If this bit is not set, the
case is preserved.  If you are intending to use your program on UNIX
systems, we recommend that you do not fold case.

This routine can accept either null-terminated or space-terminated
strings.  Setting the second least significant bit (bit 1) of
splitjoin-flg1 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-len, basename-len, and extension-len respectively, if
they are terminated with either a space or a null, depending on the
setting bit 1 of splitjoin-flg1.

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 backslash (\) or
slash (/) or colon (:)  (DOS, Windows and OS/2), and basename-buffer is
not empty, the routine inserts a backslash (\) (DOS, Windows and OS/2) or
slash(/) (UNIX) between the path and base-name in join-buffer.

If extension is ".", 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
splitjoin-flg1.

On DOS, Windows and OS/2, if path consists of a valid drive letter, but
no colon, the routine adds one.  It does not do this for a device (for
example LPT1) that does not need one.  You cannot join a device (as
opposed to a drive letter) to a non-empty base-name.

On Entry:.   

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

 splitjoin-flg1     bit 1 = 1 the strings are null-terminated
                    = 0 the strings are space-terminated.
                    bit 0 = 1 the new file-name is folded to
                    upper case
                    = 0 the original case is preserved.

 path-strt          Offset of the start of the path in path-buffer,
                    indexed from one.

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

 basename-strt      Offset of the start of the base-name in
                    basename-buffer, indexed from one.

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

 extension-strt     Offset of the start of the extension in
                    extension-buffer, indexed from one.

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

 path-buffer        Path-name.

 basename-buffer    Basename.

 extension-buffer   Extension.

 join-buf-len       Length of join-buffer.

On Exit:.   

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

 join-buffer        The joined-up file-name.

 status-code        Return status:

                    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 finds 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 section Key 

Remarks:.   

With the static linked run-time system under DOS, Windows and OS/2 this
routine does not look in libraries for files.

On Entry:.   

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

 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 is 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 should contain the
                    value that was returned in this item from the
                    previous user-mode = 1 or 2 call.

 buffer-len         Size of following buffer.

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, the contents of 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 this data item is always 0 on
                    exit.

 path-flag          Shows whether user-file-spec contained an embedded
                    environment variable that has been expanded in
                    actual-file-spec.

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

                    &>0 = 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
                    the buffer
                    4 = resulting file-name is illegal
                    255 = other error

Example:.   

user-file-spec can take the form:

Standard file-name:

DOS, Windows, and OS/2:  path\file-name.ext
UNIX: path/file-name.ext

Embedded environment variable:

DOS, Windows, and OS/2:  $envname\file-name.ext
UNIX: $envname/file-name.ext

Embedded library name:

DOS, Windows, and OS/2:  path\lbr-nam.lbr\file-nam.ext
UNIX: path/lbr-nam.lbr/file-nam.ext



MPE/iX 5.0 Documentation