call "CBL_AUDIT_EVENT" using by value     flags
                             by reference component-id
                             by reference audit-event
                                returning status-code 
               		| Typedef | Picture | |
|---|---|---|
| flags | cblt-x4-comp5 | pic x(4) comp-5 | 
| component-id | pic x(n) | pic x(n) | 
| audit-event | cblt-aud-event | Group containing | 
| cblte-audevt-version | cblt-x4-comp5 | pic x(4) comp-5 | 
| cblte-audevt-flags | cblt-x4-comp5 | pic x(4) comp-5 | 
| cblte-audevt-id | cblt-x4-comp5 | pic x(4) comp-5 | 
| cblte-audevt-category | cblt-x4-comp5 | pic x(4) comp-5 | 
| cblte-audevt-data-count | cblt-x4-comp5 | pic x(4) comp-5 | 
| cblte-audevt-reserved1 | cblt-x4-comp5 | pic x(4) comp-5 occurs 7 | 
| cblte-audevt-event-len | cblt-pointer | pointer | 
| cblte-audevt-event-type | cblt-pointer | pointer | 
| cblte-audevt-event-data | cblt-pointer | pointer | 
| cblte-audevt-reserved2 | cblt-pointer | pointer occurs 7 | 
Control flags
| Bit | Value | Meaning | 
|---|---|---|
| 0-12 | Reserved | for future use (must be 0) | 
| 13 | 0 | cblte-audevt-event-data is an array of pointers to trace data of varying size and type. The corresponding elements of the cblte-audevt-event-len and cblte-audevt-event-type arrays need to be set up. | 
| 1 | cblte-audevt-event-data is an array of pointers to trace data of the same size and type. Only the first element of cblte-audevt-event-len and cblte-audevt-event-type need to be set up. | |
| 14-29 | Reserved for future use (must be 0) | |
| 30 | 0 | component-id is space-terminated | 
| 1 | component-id is null-terminated | |
| (ignored if bit 31 unset) | ||
| 31 | 0 | component-id is an audit handle created by CBL_AUDIT_HANDLE_GET (pic x(4) comp-5). | 
| 1 | component-id is a text string (pic x(n)) . The termination character for the string is defined by bit 30. | 
Value Category 0 Unknown 1 Audit Facility 2 System 3 Security API request check 4 Security API request define 5 Security API request other 6 Security API result allow 7 Security API result deny 8 Security API result error 9 Security API result success
Value Type 0 Binary 1 Text (local encoding) 2 Address 3 COMP-5 4 COMP-X 5 UTF8 6 Signed COMP-5 7 Signed COMP-X
N.B. for address type items, the array element is the address value, and not a pointer to the address value.
Nothing
| 78-AUD-RET-SUCCESS | 
| 78-AUD-RET-INVALID-HANDLE | 
| 78-AUD-RET-INVALID-AUDIT-CATEGORY | 
| 78-AUD-RET-NOT-ENOUGH-MEMORY | 
| 78-AUD-RET-OUTPUT-ERROR | 
| 78-AUD-RET-INVALID-COMPONENT-NAME | 
| 78-AUD-RET-NO-SERVER-PROCESS | 
| 78-AUD-RET-ACCESS-DENIED | 
| 78-AUD-RET-TIMEDOUT | 
copy "mfaudit.cpy".
78 78-EVENT-TYPE-A      value 1.
78 78-EVENT-TYPE-B      value 2.
01 audit-event          cblt-aud-event.
01 audit-event-lengths  pic x(4) comp-5 occurs 1.
01 audit-event-pointers pointer occurs 1.
01 audit-event-types    pic x(4) comp-5 occurs 1.
01 audit-handle         pic x(4) comp-5.
01 audit-info           pic x(10).
01 component-id         pic x(7) value "mycomp ".
01 flags                pic x(4) comp-5.
...
move low-values to audit-event
set cblte-audevt-event-len of audit-event to
    address of audit-event-lengths(1)
set cblte-audevt-event-type of audit-event to
    address of audit-event-types(1)
set cblte-audevt-event-data of audit-event
    to address of audit-event-pointers(1)
 
               		1) Acquire an audit handle to trace "mycomp" component audit events, and then output two audit events: one with event data, one without.
call "CBL_AUDIT_HANDLE_GET" using by value 0
                                  by reference component-id
                                  by reference audit-handle
...
move 0 to flags
move 78-AUD-FLAG-CATEGORY-UNKNOWN to
     cblte-audevt-category of audit-event
move 78-EVENT-TYPE-A to cblte-audevt-id of audit-event
move 1 to cblte-audevt-data-count of audit-event
move length of audit-info to audit-event-lengths(1)
move 78-AUDIT-EVENT-TYPE-TEXT to audit-event-types(1)
set audit-event-pointers(1) to address of audit-info
call "CBL_AUDIT_EVENT" using by value flags 
                             by reference audit-handle
                             by reference audit-event
...
move 78-EVENT-TYPE-B to cblte-audevt-id of audit-event
move 0 to cblte-audevt-data-count of audit-event
call "CBL_AUDIT_EVENT" using by value flags 
                             by reference audit-handle
                             by reference audit-event
...
 
               		2) Output two informational events for the "mycomp" component without acquiring an audit handle
...
move 78-AUD-FLAG-COMPID-STRING to flags
move 78-AUD-FLAG-CATEGORY-UNKNOWN to
     cblte-audevt-category of audit-event
move 78-EVENT-TYPE-A to cblte-audevt-id of audit-event
move 1 to cblte-audevt-data-count of audit-event
move length of audit-info to audit-event-lengths(1)
move 78-AUDIT-EVENT-TYPE-TEXT to audit-event-types(1)
set audit-event-pointers(1) to address of audit-info
call "CBL_AUDIT_EVENT" using by value flags 
                             by reference component-id
                             by reference audit-event
...
move 78-EVENT-TYPE-B to cblte-audevt-id of audit-event
move 0 to cblte-audevt-data-count of audit-event
call "CBL_AUDIT_EVENT" using by value flags 
                             by reference component-id
                             by reference audit-event
...
 
 
               	 
Comments:
None