C$EXCEPINFO

C$EXCEPINFO retrieves information about an object exception that has been raised.

Usage

CALL "C$EXCEPINFO"
   USING ERROR-INFO, ERR-SOURCE, ERR-DESCRIPTION,
       ERR-HELP-FILE, ERR-HELP-CONTEXT, ERR-OBJECT-HANDLE,
       ERR-CONTROL-ID

Parameters

ERROR-INFO
Group item to receive returned information.

ERROR-INFO must have the following structure (defined in activex.def):

01 ERROR-INFO.
   03 ERROR-INFO-RESULT USAGE UNSIGNED-INT.
   03 ERROR-INFO-FACILITY USAGE UNSIGNED-SHORT.
   03 ERROR-INFO-CODE USAGE UNSIGNED-SHORT.
ERROR-INFO is described Comments in this topic.
ERR-SOURCE PIC X(n) (optional)
A text string identifying the source of the exception. Typically, this is an application name.
ERR-DESCRIPTION PIC X(n) (optional)
A text description of the error intended for the user. If no description is available, ERR-DESCRIPTION is filled with spaces.
ERR-HELP-FILE PIC X(n) (optional)
The fully qualified drive, path, and file name of a help file with more information about the error. If no help is available, ERR-HELP-FILE is filled with spaces.
ERR-HELP-CONTEXT Usage unsigned-long (optional)
The help context ID of the topic within the help file. This parameter is filled in only if the ERR-HELP-FILE parameter is not spaces. The help context ID will be between 0 and 4294967295.
ERR-OBJECT-HANDLE Usage handle (optional)
The handle of the COM object or ActiveX control that generated the exception.
ERR-CONTROL-ID Usage PIC XX COMP-X (optional)
The ID of the ActiveX control that generated the exception. The value is 0 if the object that generated the exception is not an ActiveX control.

Comments

C$EXCEPINFO is typically called from an error handling procedure specified with a Format 2 USE statement in the declaratives.

The following are the parameters for the ERROR-INFO group item:

ERROR-INFO-RESULT
is a 32-bit number identifying the error. The error number will be greater than 1000 and less than 4294967296. This error number is divided into 4 fields: a severity code, a reserved portion, a facility field, and an error code.
FACILITY-ACU (4) For status codes of exceptions raised by the ACUCOBOL-GT runtime.
FACILITY-ACTIVE-X (10) For status codes of exceptions raised by an ActiveX control.

The severity code is the high-order bit (31). The next 4 bits are reserved (30-27). The next eleven bits are the facility field (26-16), and the last sixteen bits are the error code (15-0). The severity code is usually 1, and the reserved bits are usually set to 0. The error code is defined by the facility that raised the exception. The facility field is one of the following:

The standard facility field values and error codes are defined as condition names (level 88) in activex.def.

Note: If you receive a facility value that is anything other than the two listed above, you will need to look up the ERROR-INFO result number in the documentation for the specific ActiveX control you are using or in Microsoft’s documentation.
ERROR-INFO-FACILITY

contains the facility field extracted from ERROR-INFO-RESULT.

ERROR-INFO-CODE

contains the error code extracted from ERROR-INFO-RESULT. ERROR-INFO-CODE will be listed in the ACUCOBOL-GT error codes if the facility field is FACILITY-ACU. If the facility is FACILITY-ACTIVE-X, the ERROR-INFO-CODE may be listed in an enumeration in the ActiveX control’s COPY file or it may be one of the standard COM status codes for ActiveX controls.

When called to get information about an object exception, the error code can either be an ACUCOBOL-GT defined code or a COM status code.

ACUCOBOL-GT Error Codes (defined in activex.def):

Name Description
ACU-E-UNEXPECTED Unexpected error
ACU-E-INVALIDPARAMNAME Invalid parameter name
ACU-E-INVALIDHANDLE Invalid handle
ACU-E-INITIALSTATE Error loading INITIAL-STATE from resource file
ACU-E-NOEXCEPINFO No exception information available
ACU-E-INVALIDPROPNUM Invalid property number
ACU-E-TOOMANYPARAMS Too many parameters
ACU-E-TOOFEWPARAMS Too few parameters
ACU-E-NOTPROPERTYGET Property can be modified but not inquired
ACU-E-NOTPROPERTYPUT Property can be inquired but not modified
ACU-E-CREATE Error creating ActiveX control
COM Status Codes for ActiveX controls (defined in activex.def):
Name Description
AX-E-ILLEGALFUNCTIONCALL Illegal function call
AX-E-OVERFLOW Overflow
AX-E-OUTOFMEMORY Out of memory
AX-E-DIVISIONBYZERO Division by zero
AX-E-OUTOFSTRINGSPACE Out of string space
AX-E-OUTOFSTACKSPACE Out of stack space
AX-E-BADFILENAMEORNUMBER Bad file name or number
AX-E-FILENOTFOUND File not found
AX-E-BADFILEMODE Bad file mode
AX-E-FILEALREADYOPEN File already open
AX-E-DEVICEIOERROR Device I/O error
AX-E-FILEALREADYEXISTS File already exists
AX-E-BADRECORDLENGTH Bad record length
AX-E-DISKFULL Disk full
AX-E-BADRECORDNUMBER Bad record number
AX-E-BADFILENAME Bad file name
AX-E-TOOMANYFILES Too many files
AX-E-DEVICEUNAVAILABLE Device unavailable
AX-E-PERMISSIONDENIED Permission denied
AX-E-DISKNOTREADY Disk not ready
AX-E-PATHFILEACCESSERROR Path/file access error
AX-E-PATHNOTFOUND Path not found
AX-E-INVALIDPATTERNSTRING Invalid pattern string
AX-E-INVALIDUSEOFNULL Invalid use of NULL
AX-E-INVALIDFILEFORMAT Invalid file format
AX-E-INVALIDPROPERTYVALUE Invalid property value
AX-E-INVALIDPROPERTYARRAYINDEX Invalid property array index
AX-E-SETNOTSUPPORTEDATRUNTIME Set not supported at run time
AX-E-SETNOTSUPPORTED Set not supported (read-only property)
AX-E-NEEDPROPERTYARRAYINDEX Need property array index
AX-E-SETNOTPERMITTED Set not permitted
AX-E-GETNOTSUPPORTEDATRUNTIME Get not supported at run time
AX-E-GETNOTSUPPORTED Get not supported (write-only property)
AX-E-PROPERTYNOTFOUND Property not found
AX-E-INVALIDPICTURE Invalid clipboard format
AX-E-PRINTERERROR Printer error
AX-E-CANTSAVEFILETOTEMP Can’t save file to TEMP
AX-E-SEARCHTEXTNOTFOUND Search text not found
AX-E-REPLACEMENTSTOOLONG Replacements too long

For an example of how this works, let’s look at the standard COM error code for Out of Memory.

The code is hex 800A0007.

In binary this is “1000 0000 0000 1010 0000 0000 0000 0111”.

This error code can be broken down as follows:

1 000 0 000 0000 1010 0000 0000 0000 0111
Severity Code Reserved Facility Field Error Code

The severity code is 1 which makes ERROR-INFO-RESULT greater than or equal to 2147483648 (hex 80000000). The reserved portion is 0. The facility code is 10 (hex A) which is defined in activex.def as FACILITY-ACTIVE-X. The error code is 7 (hex 7) which is defined in activex.def as AX-E-OUTOFMEMORY.

Example

DATA DIVISION.
WORKING-STORAGE SECTION.
COPY "ACTIVEX.DEF"
77 ERR-SOURCE           PIC X(30).
77 ERR-DESCRIPTION      PIC X(200).
77 ERR-HELP-FILE        PIC X(200).
77 ERR-HELP-CONTEXT     USAGE UNSIGNED-LONG.
77 CHOICE               PIC 9.

PROCEDURE DIVISION.
DECLARATIVES.
OBJECT-EXCEPTION-HANDLING SECTION.
    USE AFTER EXCEPTION ON OBJECT.
OBJECT-EXCEPTION-HANDLER.
    CALL "C$EXCEPINFO" USING ERROR-INFO, ERR-SOURCE,
        ERR-DESCRIPTION, ERR-HELP-FILE,
        ERR-HELP-CONTEXT.
    IF ERR-HELP-FILE = SPACES THEN
        DISPLAY MESSAGE BOX ERR-DESCRIPTION
            TITLE ERR-SOURCE
            ICON MB-ERROR-ICON
    ELSE
        DISPLAY MESSAGE BOX ERR-DESCRIPTION H'0d'
            "Do you want help ?"
            TITLE ERR-SOURCE
            ICON MB-ERROR-ICON
            TYPE IS MB-YES-NO
            DEFAULT IS MB-YES
            GIVING CHOICE
    IF CHOICE = 1 THEN
        CALL "$WINHELP" USING ERR-HELP-FILE, HELP-CONTEXT
            ERR-HELP-CONTEXT
    END-IF
END-IF.
EVALUATE TRUE
    WHEN FACILITY-ACU
        EVALUATE TRUE
            WHEN ACU-E-UNEXPECTED
                STOP RUN
            END-EVALUATE
        END-EVALUATE.
END DECLARATIVES.

MAIN-PROGRAM SECTION.
{ . . . }
* The following line causes an AX-E-SETNOTSUPPORTEDATRUNTIME
* exception since Microsoft Chart's BorderStyle property is not
* allowed to be modified at runtime
    MODIFY MS-CHART-1 BorderStyle = VtBorderStyleBold.