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

On Entry:.   

 screen-position    The screen position at which to start reading.  The
                    top left corner is row 0, column 0.  See Notes on 
                    Screen Routines.

 string-length      The length of the string to read.

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

Remarks:.   

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

See Introduction to Heap Routines  

On Entry:.   

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

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

 heap-len           Number of bytes to read.

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

On Entry:.   

 old-file-name      The file to rename.  The name can contain a
                    path-name, and is terminated by a space.  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 if a file of the
                    name in new-file-name already exists.

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

On Entry:.   

 screen-position    The screen position at which to put the cursor.  The
                    top left corner is row 0, column 0.  To make the
                    cursor invisible, set row-number and column-number to
                    255.  Any other legal on-screen values make the
                    cursor visible.

                    See Notes on Screen Routines.

On Exit:.   

None

CBL_SET_MOUSE_MASK 

Sets the mouse event mask.

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

Remarks:.   

This routine has no effect in UNIX environments.

CBL_GET_MOUSE_MASK should be called first to find out which events are
enabled.

See Introduction to Mouse Routines.

On Entry:.   

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

 event-mask         See Introduction to Mouse Routines 

On Exit:.   

None

CBL_SET_MOUSE_ POSITION 

Moves the mouse pointer.

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

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

On Exit:.   

None

CBL_SHOW_MOUSE 

Makes the mouse pointer visible.

Syntax:.   

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

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.  This routine cancels any
collision area defined earlier by PC_SET_MOUSE_HIDE_AREA.

See Introduction to Mouse Routines.

On Entry:.   

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

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-param
         split-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.
split-buffer        PIC X(n).
status-code         See section Key 

Remarks:.   

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

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 period (.)  and the end of the file-name.  The base-name contains
everything up to, but not including, the last period (.).

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
period (.)), if the extension is spaces, extension-len is 1 and
extension-strt points to the last period (.).

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 file-name is null-terminated
                    = 0 the file-name is space-terminated.
                    bit 0 = 1 the new strings are folded to upper case
                    = 0 the original case is 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.

On Exit:.   

 splitjoin-flg2     bit 1 = 1 there is a wildcard in the path
                    bit 0 = 1 there is a wildcard in base-name or
                    extension

 path-strt          Start of path-name in split-buffer, from one.

 path-len           Length of path-name; zero if there is none.  This
                    includes any following colon (:)  (DOS, Windows and
                    OS/2).

 basename-strt      Start of base-name in split-buffer, from one.

 basename-len       Length of base-name; zero if there is none.  This
                    does not include the following period (.).

 extension-strt     Start of extension in split-buffer, from one.

 extension-len      Length of extension; zero if there is none.  This
                    does not include the preceding period (.).

 total-length       Total number of characters in the string.

 first-path-len     Number of characters up to and including the first
                    backslash (\), slash (/) or colon (:)  (DOS, Windows
                    and OS/2); if split-buffer contains none of these,
                    this field = path-len.

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

 status-code        Return status:

                    0 = success
                    4 = illegal file-name

CBL_SUBSYSTEM 

Declares or deallocates subsystems - groups of programs.

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
Withfunction-code
= 0
 parameter          Group item defined as:
      ss-handle     PIC X(2) COMP-X.
      ss-name-len   PIC X(2) COMP-X.
      ss-name       PIC X(n).
Withfunction-code
= 1
    parameter       PIC X(2) COMP-X.
With function-code
= 2
    parameter       PIC X(2) COMP-X VALUE 0.
 status-code        See Key 

Remarks:.   

This routine is not available when using the static linked run-time
system under DOS, Windows and OS/2.  A program containing a call to this
routine will link correctly, but the call will have no effect.

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 is only 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.

On Entry:.   

 function-code      The subfunction number.

With function-code = 0

   ss-name-len      The length of subsystem program-name field.

   ss-name          The subsystem program-name (space- terminated).  This
                    must be a COBOL .int or .gnt module.

With function-code = 1

   ss-handle        The subsystem handle returned by a function 0 call.

With function-code = 2

 dummy-param        Value 0.

On Exit:.   

With function-code = 0

   ss-handle        The subsystem handle.

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

On Entry:.   

 screen-position    The screen position at which to start writing.  The
                    top left corner is row 0, column 0.  See Notes on 
                    Screen Routines.

 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.

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 

Terminates mouse support, releasing internal resources.

Syntax:.   

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

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 results in an error.

See Introduction to Mouse Routines.

On Entry:.   

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

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

Remarks:.   

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

On Entry:.   

 string             The string to convert.

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

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

Remarks:.   

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

On Entry:.   

 string             The string to convert.

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

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

Remarks:.   

See Introduction to Byte-stream Routines  

On Entry:.   

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

 file-offset        The offset in the 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 causes 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 64K
                    segment boundary.

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

On Entry:.   

 screen-position    The screen position at which to start writing.  The
                    top left corner is row 0, column 0.  See Notes on 
                    Screen Routines.

 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.

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

On Entry:.   

 screen-position    The screen position at which to start writing.  The
                    top left corner is row 0, column 0.  See Notes on 
                    Screen Routines.

 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.

On Exit:.   

None



MPE/iX 5.0 Documentation