Titus Information Systems, Inc.

Standard Library
COBOL Functions

These routines are designed to be called from any language.  They have been thoroughly tested with the MicroFocus NetExpress COBOL compiler.

Many of these routines pass character strings in the "CHAR(*)VAR" format.  This is a non-terminated string format with the first two bytes containing the number of characters (the length of the string).  The following is an example of a DATA DIVISION excerpt that demonstrates a sample string:

       01  PASSED-BUFFER.
           03  STRING-LENGTH   PIC S9999 USAGE COMP-5 VALUE 14.
           03  STRING-CHARS    PIC X(14) VALUE 'This is a test'.
Many of these functions return a value as well as operating on the arguments.  The value of the function will be in RETURN-CODE (if called with COBOL), which should be set to a 16-bit integer (short).  Note that all arguments are passed by reference since these functions are designed to be used with COBOL CALL-CONVENTION 8.

Following are the descriptions of these routines:
DLSP$O – Delete Multiple Spaces
This routine deletes multiple spaces from a string buffer.  It is called with one argument, the string buffer in VAR(*)CHAR format.  The user may force multiple spaces (up to nine) by putting the vertical bar character '|' followed by the number of spaces to be left in that position.  The string is always left justified (a beginning space may be forced with the vertical bar).  The algorithm will be in two passes: the first will remove all multiple spaces ignoring the vertical bars; the second will (from right to left) add spaces depending on the vertical bar commands.  In the event the vertical bar makes the string too large for the buffer, the last vertical bar encountered will be replaced and the forcing discontinued at that point.  By starting a string with enough '|9's, the user may right justify the text.
DVER$O – Display Version
This routine displays the version and copyright message on the console.  It should be used only for console applications and is normally called at application initialization.  It is called with one argument, the application name in VAR(*)CHAR format.
EDIT$O – Edit Character String
This routine is called with three arguments, StringData, OriginalData, and ReplaceData, all in VAR(*)CHAR format.  It edits StringData replacing all occurrences of OriginalData with ReplaceData.  The value of the function is the number of replacements performed.
EXST$O – Check File Exists
This routine checks for the existence of the specified file.  The path of the file should be in the first argument in CHAR(*)VAR format.  If the file exists, the value of the function is zero.  If the file does not exist, the value of the function is the error code returned from the windows system call.
FIXF$O – Fix File Name
This routine replaces all control characters (non-printables) and those which are not legal for DOS file names in the buffer with a space.  It is called with one argument, the file name in CHAR(*)VAR format.
JSTR$A – Justify String
This routine justifies the specified string.  It is called with three arguments: Key, String, and Length.  Key is a PIC S9999 USAGE COMP-5 (16-bit integer) that specifies the operation.  String is a PIC X(n).  Length is a PIC S9999 USAGE COMP-5 (16-bit integer) that specifies the length of String in characters.
Key = 1:Right justify String
Key = 2:Left justify String
Key = 3:Center the String
Key = 4:Left justify String removing all spaces
Key = 5:Right justify String with zero fill; i.e., convert to numeric
LOADFILE – Load Binary File
This routine loads an entire file into the specified buffer.  It is called with four arguments: FileName, Length, Count, and Buffer.  FileName is a PIC X(n) that specifies the name of the file to be read; it must be null-terminated.  Length is a PIC S9(9) USAGE COMP-5 (32-bit integer) that specifies the length of each record in characters.  Count is a PIC S9(9) USAGE COMP-5 (32-bit integer) that specifies the number of records in the file.  Buffer is a PIC X(n) that specifies the memory into which the file should be loaded; it must be at least Length * Count characters is size.
LOCS$O – Convert to Lower Case
This routine converts a buffer from upper case to lower case.  It is called with two arguments, InOption and Buffer.  InOption is a PIC S9999 USAGE COMP-5 (16-bit integer).  Buffer is CHAR(*)VAR.  The conversion is as follows:
InOption = 1:Convert all upper case letters to lower case
InOption = 2:Convert all upper case letters except the first one after a period to lower case
InOption = 3:Convert all upper case letters except the one immediately following a blank to lower case
InOption = 4:Convert all upper case letters except the one immediately following a blank or a lower case letter to lower case
InOption = 5:Convert all upper case letters except the one immediately following a non-upper case letter to lower case unless the word begins with "MC"
InOption = 6:Convert all upper case letters except the one immediately following a non-upper-case letter and a non-number
InOption = 7:Convert all upper case letters except the one immediately following a non-upper-case letter unless the next two characters are "ST", "ND", "RD", OR "TH"
MCHR$A – Move Character
This routine moves a character from one string to another.  It is called with four arguments: the receiving string in PIC X(n) format; the receiving character position in that string in PIC S9999 USAGE COMP-5 (16-bit integer) format; the sending string in PIC X(n) format; and the sending character position in PIC S9999 USAGE COMP-5 (16-bit integer) format.
MFNT$A – Make Fixed-length from Null-Terminated
This routine makes a fixed length String from a null-terminated one.  It finds the first null in the String and replaces it and all subsequent characters in the String with blanks.  The value of the function is the original String length.  It is called with two arguments: the string in PIC X(n) format, and the length of the string buffer in PIC S9999 USAGE COMP-5 (16-bit integer) format.
MFNT$O – Make Fixed-length from Null-Terminated
This routine makes a fixed length String from a null-terminated one.  It finds the first null in the String and replaces it and all subsequent characters in the String with blanks.  The value of the function is the original String length.  It is called with one argument: the string buffer in CHAR(*)VAR format.
MSTR$A – Move String
This routine moves copies a character string.  It is called with four arguments: the sending string in PIC X(n) format, the length of the sending string in PIC S9999 USAGE COMP-5 (16-bit integer) format, the receiving string in PIC X(n) format, and the length of the receiving string in PIC S9999 USAGE COMP-5 (16-bit integer) format.  If the two strings are not the same length, the sending string will be truncated or blank filled as appropriate.
MSUB$A – Move Sub-string
This routine moves one substring to another substring.  It is called with eight arguments: the sending character string, the length of the sending string buffer, the starting character position, the ending character position, the receiving character string, the length of the receiving string buffer, the starting character position, and the ending character position.  The two strings are in PIC X(n) format, and the two lengths and four positions are in PIC S9999 USAGE COMP-5 (16-bit integer) format.  If the two sets of starting and ending positions do not specify a substring of the same length, the sending substring will be truncated of blank filled as appropriate.
MVNT$A – Move Variable-length Null-terminated String
This routine makes a variable length null-terminated string from a fixed- length blank-filled character string buffer.  It appends a null to the end of the text in the specified string.  The end of the text is determined by scanning from the end of the string to the first non-blank character.  It is called with two arguments: the string in PIC X(n) format, and the length of the string buffer in PIC S9999 USAGE COMP-5 (16-bit integer) format.
MVNT$O – Move Variable-length Null-terminated String
This routine makes a variable length null-terminated string from a fixed- length blank-filled character string buffer.  It appends a null to the end of the text in the specified string.  The end of the text is determined by scanning from the end of the string to the first non-blank character.  It is called with one argument: the string buffer in CHAR(*)VAR format.
NLEN$A – Get Length of String
This routine returns the length of the specified string.  Note: if the original length of the string buffer is positive, the string length without trailing spaces will be returned; if the original length of the string buffer is negative, the string length without trailing control characters will be returned.  It is called with two arguments: the string in PIC X(n) format, and the length of the string buffer in PIC S9999 USAGE COMP-5 (16-bit integer) format.  The value of the function is the string length.  The original string length is unchanged.
NLEN$O – Get Length of String
This routine returns the length of the specified string.  Note: if the original length of the string buffer is positive, the string length without trailing spaces will be returned; if the original length of the string buffer is negative, the string length without trailing control characters will be returned.  It is called with one argument: the string buffer in CHAR(*)VAR format.  Note that the function does not have a value.  The original string length is modified by the function.
OPEN$O – Open a File
This routine presents the common file dialog box and returns the selected file name information.  The arguments are as follows:
Filters: Array of file filters (extensions).  The format is a series of null-terminated strings terminated with a second null after the last string.
FileName: Buffer for file name returned.  Note that if a path and file are specified upon entry, the dialog box will be initialized with them.  Both the specified and returned pathname will be null terminated.  The buffer size is specified in the option block below.
WinTitle: Dialog box window title as a null-terminated string.
Option: as follows:
03  PARENT-WINDOW-HANDLE       PIC S9(9) USAGE COMP-5.
03  PARENT-INSTANCE-HANDLE     PIC S9(9) USAGE COMP-5.
03  FNAMES-MAX-BUFFER-SIZE     PIC S9999 USAGE COMP-5.
    88  POSITIVE IS OPEN (INPUT)
    88  NEGATIVE IS SAVE AS (OUTPUT)
03  DIALOG-BOX-FUNCTION-RESULT PIC S9999 USAGE COMP-5.
    88  SUCCESS                VALUE 1.
03  FILE-NAME-WITHOUT-PATH     PIC X(14).
This routine may also be called from
Visual Basic for Applications.  Use the following header:
Declare Function WordGetFileName Lib "TISLIBP.DLL" (ByVal Filters As String, ByVal PathName As String, ByVal Title As String, ByVal Size As Long, ByVal FileName As String) As Long

Use the following code to call the declared function:
Dim Filters As String
Dim FileName As String
Dim FilePath As String
Filters = "All Files (*.*)" + Chr(0) + "*.*" + Chr(0)
FileName = String(14, " ")
FilePath = String(160, " ")
Result = WordGetFileName(Filters, FilePath, "Window Title", 160, FileName)

Note:  FilePath and FileName will have training spaces to the length of the field; use Trim(FilePath) if necessary.  Also, while FileName must be 14 characters, the length of FilePath may be changed from 160 if necessary.
PMRG$O – Parse a Mail-merge File
This routine parses a PC "merge" record (comma-delimited) according to the description given into fixed-length space-filled fields.  Arguments are as follows:
MergeRecord: CHAR(*)VAR
Pattern: short array; count followed by lengths
ResultFields: Concatenated fields

The following example parses a comma-delimited record containing three fields, number, name, and description, into the respective fixed fields.  After the function call, if OR-RECORD contained 642,John Doe,"This is a test", PR- NUMBER will contain 642, PR-NAME will contain John Doe, and PR- DESCRIPTION will contain This is a test.
              CALL-CONVENTION 8 IS VCPP.
          01  ORIGINAL-RECORD.
              03  OR-LENGTH          PIC S9999 USAGE COMP-5 VALUE 80.
              03  OR-RECORD          PIC X(80).
          01  MERGE-PATTERN.
              03  MP-COUNT           PIC S9999 USAGE COMP-5 VALUE 3.
              03  MP-NUMBER          PIC S9999 USAGE COMP-5 VALUE 6.
              03  MP-NAME            PIC S9999 USAGE COMP-5 VALUE 30.
              03  MP-DESCRIPTION     PIC S9999 USAGE COMP-5 VALUE 50.
          01  PARSED-RECORD.
              03  PR-NUMBER          PIC X(6).
              03  PR-NAME            PIC X(30).
              03  PR-DESCRIPTION     PIC X(50).
              CALL VCPP 'PMRG$O' USING ORIGINAL-RECORD, MERGE-PATTERN,
                  PARSED-RECORD.
SDIS$O – Standard Display
This routine creates a text file in the format compatible with the SDIS (Standard Display) routines.  It is called with two arguments, a Key in PIC S9999 USAGE COMP-5 format, and a Buffer the contents of which vary depending Key.  The following table lists the valid Keys and the corresponding CSDisCreate member function invoked.  The CSDisCreate::ReturnCode data member is placed in RETURN-CODE.
Key = 1: CSDisCreate::Open(Buffer)
Key =2: CSDisCreate::Close()
Key =3: CSDisCreate::StartFile(Buffer)
Key =4: CSDisCreate::EndFile()
Key =5: CSDisCreate::StartPage(Buffer)
Key =6: CSDisCreate::EndPage()
Key =7: CSDisCreate::StartLine(Buffer)
Key =8: CSDisCreate::EndLine()
Key =9: CSDisCreate::Packet(Buffer)
Key =10: CSDisCreate::CompleteLine(Buffer);

SHPK$O – Shift Packed Decimal Field
This routine converts a buffer from unsigned packed decimal to signed packed decimal by shifting all nybbles left and adding a hexadecimal C (0xC) to the rightmost nybble.  Note that the high-order nybble will be lost.  It is called with two arguments: the field length in bytes, not nybbles, and the packed decimal field.
TABLEFIL – Load Table File
This routine loads an entire file into the specified buffer.  Both the file and memory buffer must start with a PIC S9999 USAGE COMP-5 (16-bit integer) that specifies the number of records in the table.  It is called with two arguments: Key and Buffer.  Key is a PIC S9999 USAGE COMP-5 (16-bit integer) that specifies the operation (see table below).  Buffer specifies the memory buffer for the operation as follows:
Key = 0:Load the name of the table file from Buffer, which is a PIC X(n) and is space-terminated.
Key = 1:Set the length of each record from Buffer, which is a PIC S9999 USAGE COMP-5 (16-bit integer).
Key = 2:Set the address of the memory buffer to be used for all file operations from Buffer.
Key = 3:Load the contents of the file into the memory buffer and close the file.
Key = 4:Store the contents of the memory buffer into the file and close it.
Key = 5:Read the contents of the file into the memory buffer and leave the file open for use by Key = 6.
Key = 6:Write the contents of the memory buffer into the file opened by Key = 5 and close it.
TDAT$O – Transfer Data File
This routine performs file I/O for a Transfer Data File.  It is called with two arguments, a Key in PIC S9999 USAGE COMP-5 (16-bit integer) format, and a Buffer in the CHAR(*)VAR format the contents of which vary depending Key.  This file contains records for various files (tables) in a database.  The file code and record length are stored in the Transfer Data File for each record.  Using this file, entire databases or portions thereof may be moved from one storage medium to another or from one filing system to another.  The following table lists the valid Keys and the corresponding CTransfer member function invoked.
Key = 1: CTransferData::Open(Key, Buffer, CFile::modeCreate | CFile::modeWrite | CFile::shareDenyWrite)
Key = 2: CTransferData::Write(Buffer)
Key = 3: CTransferData::Close()
Key = 4: CTransferData::Open(Key, Buffer, CFile::modeRead | CFile::shareDenyNone)
Key = 5: CTransferData::Read(Buffer)
Key = 6: CTransferData::Close()


[ Stand-alone Programs | Standard Library | Conversion Functions | Utility Functions ]
[ Windows NT Library | COBOL Library | COBOL Interface | Command Prompt Abbreviations | Purchase Instructions ]

[ Home | Areas of Expertise | "We Do Windows" | Clients and Projects | Software Samples | Package Software Available ]
[ Contact Information | Business Software Philosophy | Church Software Philosophy ]
All contents of this web site are Copyright © Titus Information Systems, Inc., Phoenix, Arizona, U.S.A.