MDTest Functions
Pre-Requisites
Ensure the prerequisites below are met before adding MDTest Test Functions described below to your test programs.
COBOL
- In Working Storage Section
COPY MDTCBLWSC OF QLBLSRC.
- In Procedure Division
COPY MDTCBLPRC OF QLBLSRC.
- Bind in MDTEST/MDRTEST Service Program (Use any preferred method)
- Ensure MDTEST is in the library list when compiling the program.
RPG
- Include the follwing copy book:
/Copy QRPGLESRC,MDRTESTP
- Bind in MDTEST/MDRTEST Service Program (Use any preferred method)
- Ensure MDTEST is in the library list when compiling the program.
MDTest Procedures
Help Functions
MDTest_addInfo
writes an Information Entry to Result
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
In | Message | VarChar(128) | Value | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-ADDINFO USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
In | MDTEST-MSG | PIC X(128) | No | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
Dcl-S h_Message VarChar(128);
//Version 1
h_Message = 'This is my';
MDTest_addInfo(h_Message + ' first message');
//Version 2
MDTest_addInfo('This is my second message':'FINANCE');
MDTest_addPassResult
writes a Pass Result
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
In | Message | VarChar(128) | Value | |
In | Expected Value | VarChar(4096) | Const, NoPass, Omit | |
In | Actual Value | VarChar(4096) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-ADDPASSRESULT USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
In | MDTEST-MSG | PIC X(128) | No | each Call | |
In | MDTEST-EXP-NUM | PIC X(4096) | Yes | each Call | |
In | MDTEST-ACT-NUM | PIC X(4096) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
Chain 16 CUSTOMER;
If %found(CUSTOMER);
MDTest_addPassResult('Customer record found.':'Customer':'exists');
EndIf;
MDTest_addLogEntry
writes a Log Entry
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Log Entry Id | Int(10) | Input Parameter for MDTest_addLogDetailEntry | |
In | Message | VarChar(2048) | Value |
COBOL SECTION
MDTEST-ADDLOGENTRY USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-LOG-ID | PIC S9(9) COMP-5 | Output Parameter of MDTest_addLogEntry | ||
In | MDTEST-LOG-MSG | PIC X(2048) | No | each Call |
RPG Example
Dcl-S h_LogEntryId Like(MDTest_addLogEntry);
h_LogEntryId = MDTest_addLogEntry('Check of Procedure getCustomer finished.');
MDTest_addLogDetailEntry
writes a Log Detail Entry
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
In | Log Entry Id | Int(10) | Value | Output Parameter of MDTest_addLogEntry |
In | Message | VarChar(2048) | Value |
COBOL SECTION
MDTEST-ADDLOGDETAILENTRY USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
In | MDTEST-LOG-ID | PIC S9(9) COMP-5 | No | first only | Output Parameter of MDTest_addLogEntry |
In | MDTEST-LOG-MSG | PIC X(2048) | No | each Call |
RPG Example
Dcl-S h_LogEntryId Like(MDTest_addLogEntry);
MDTest_addLogDetailEntry(h_LogEntryId:'Paremter used for calling getCustomer: 16');
MDTest_getJobStatus
returns the current Job status
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL, MDTest_PASS or MDTEST_UNKNOWN |
COBOL SECTION
MDTEST-GETJOBSTATUS USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL, MDTEST-PASS or MDTEST-UNKNOWN |
RPG Example
MDTest_forceFail
writes a Fail Result
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
In | Message | VarChar(128) | Value | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-FORCEFAIL USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
In | MDTEST-MSG | PIC X(128) | No | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
MDTest_abortBatch
writes a Fail Result
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
In | Message | VarChar(128) | Value | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-ABORTBATCH USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
In | MDTEST-MSG | PIC X(128) | No | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
MDTest_waitManualStep
Wait for manual actions - Allows for test steps, such as interactive processes, to occur outside of the MDTest framework and then log the test status decision provided by a user from within MDOpen.
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
In | Timeout | Int(10) | Const, NoPass, Omit | Maximum wait time in seconds |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-WAIT-MANUAL-STEP USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
In | MDTEST-TIMEOUT | PIC S9(9) COMP-5 | Yes | each call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
Execute Functions
MDTest_Start_Timer
Start the timer for performance measurement and set the start-point for any job log messages to be reported.
After the timer is started, perform one or more program calls, procedure calls, etc. and then use MDTest_End_Timer to stop the timer and collect the results.
When using MDTest_Execute_CMD or MDTest_Execute_SQL, the timer start/stop procedures should be omitted as they are integrated with those 2 execution functions.
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Severity | Packed(2:0) | Value | Severity of Messages to log |
In | Duration | Int(10) | Const, NoPass, Omit | Allowed duration in milliseconds between start and end of timer |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-START-TIMER USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-SEV | PIC S9(2) COMP-3 | No | first only | Severity of Messages to log |
In | MDTEST-MAX-DURATION | PIC S9(9) COMP-5 | Yes | each Call | Allowed duration in milliseconds |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
MDTest_End_Timer
End the timer that was started using MDTest_Start_Timer and collect any reporting data.
If the duration between the start and end of the timer exceeds the max duration provided to the start procedure, this procedure will return MDTest_FAIL.
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-END-TIMER USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
MDTest_Execute_CMD
executes an IBM i Command
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Command | VarChar(2048) | Value | |
In | Severity | Packed(2:0) | Value | Severity of Messages to log |
In | Duration | Int(10) | Const, NoPass, Omit | Allowed duration in milliseconds |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-EXECUTE-CMD USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-CMD | PIC X(2048) | No | each Call | |
In | MDTEST-SEV | PIC S9(2) COMP-3 | No | first only | Severity of Messages to log |
In | MDTEST-MAX-DURATION | PIC S9(9) COMP-5 | Yes | each Call | Allowed duration in milliseconds |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
If MDTest_Execute_CMD('ADDLIBLE CUSTDATA':10:360) = MDTest_FAIL;
//couldnt add CUSTDATA to Library List
EndIf;
MDTest_Execute_SQL
executes an SQL Statement
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Statement | VarChar(2048) | Value | |
In | Severity | Packed(2:0) | Value | Severity of Messages to log |
In | Duration | Int(10) | Const, NoPass, Omit | Allowed duration in milliseconds |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-EXECUTE-SQL USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-CMD | PIC X(2048) | No | each Call | |
In | MDTEST-SEV | PIC S9(2) COMP-3 | No | first only | Severity of Messages to log |
In | MDTEST-MAX-DURATION | PIC S9(9) COMP-5 | Yes | each Call | Allowed duration in milliseconds |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
If MDTest_Execute_SQL('UPDATE CUST set CUSTNAME = '' WHERE CUSTNBR = 16':10:360) = MDTest_FAIL;
//couldnt update field CUSTNAME in file CUST
EndIf;
Numeric Functions
MDTest_Num_Equal
checks if "Expected Value" & "Actual Value" contain the same value
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Expected Value | Packed(63:23) | Value | |
In | Actual Value | Packed(63:23) | Value | |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-NUM-EQUAL USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-EXP-NUM | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-ACT-NUM | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
Dcl-S h_Result Like(MDTest_Num_Equal);
h_Result = MDTest_Num_Equal(CUSTNBR:16:'Customer Nbr should be 16.':'FINANCE');
MDTest_Num_NotEqual
checks if "Expected Value" & "Actual Value" contain different values
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Expected Value | Packed(63:23) | Value | |
In | Actual Value | Packed(63:23) | Value | |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-NUM-NOTEQUAL USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-EXP-NUM | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-ACT-NUM | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
Dcl-S h_Result Like(MDTest_Num_NotEqual);
h_Result = MDTest_Num_NotEqual(CUSTNBR:16:'Customer Nbr should NOT be 16.':'FINANCE');
MDTest_Num_Zero
checks if "Actual Value" is zero
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Actual Value | Packed(63:23) | Value | |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-NUM-ZERO USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-ACT-NUM | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
MDTest_Num_NotZero
checks if "Actual Value" is not zero
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Actual Value | Packed(63:23) | Value | |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-NUM-NOTZERO USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-ACT-NUM | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
MDTest_Num_LowerThan
checks if "Actual Value" is lower than "Expected Value"
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Expected Value | Packed(63:23) | Value | |
In | Actual Value | Packed(63:23) | Value | |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-NUM-LOWERTHAN USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-EXP-NUM | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-ACT-NUM | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
MDTest_Num_LowerEqualThan
checks if "Actual Value" is lower than or equal "Expected Value"
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Expected Value | Packed(63:23) | Value | |
In | Actual Value | Packed(63:23) | Value | |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-NUM-LOWEREQUALTHAN USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-EXP-NUM | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-ACT-NUM | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
MDTest_Num_GreaterThan
checks if "Actual Value" is greater than "Expected Value"
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Expected Value | Packed(63:23) | Value | |
In | Actual Value | Packed(63:23) | Value | |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-NUM-GREATERTHAN USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-EXP-NUM | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-ACT-NUM | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
MDTest_Num_GreaterEqualThan
checks if "Actual Value" is greater than or equal "Expected Value"
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Expected Value | Packed(63:23) | Value | |
In | Actual Value | Packed(63:23) | Value | |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-NUM-GREATEREQUALTHAN USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-EXP-NUM | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-ACT-NUM | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
Dcl-S h_Result Like(MDTest_Num_GreaterEqualThan);
h_Result = MDTest_Num_GreaterEqualThan(CUSTNBR:16);
MDTest_Num_InRange
checks if "Actual Value" is between "Range Start" and "Range End"
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Actual Value | Packed(63:23) | Value | |
In | Range Start | Packed(63:23) | Value | |
In | Range End | Packed(63:23) | Value | |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-NUM-INRANGE USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-ACT-NUM | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-RANGE-START | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-RANGE-END | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
MDTest_Num_OutsideRange
checks if "Actual Value" is not between "Range Start" and "Range End"
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Actual Value | Packed(63:23) | Value | |
In | Range Start | Packed(63:23) | Value | |
In | Range End | Packed(63:23) | Value | |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-NUM-OUTSIDERANGE USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-ACT-NUM | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-RANGE-START | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-RANGE-END | PIC S9(40)V9(23) | No | each Call | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
Character Functions
MDTest_Char_Equal
checks if "Expected Value" & "Actual Value" contain the same value
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Expected Value | VarChar(4096) | Value | |
In | Actual Value | VarChar(4096) | Value | |
In | Ignore Case | Ind | Const, NoPass, Omit | Case Insensitive On/Off |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-CHAR-EQUAL USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-EXP-CHAR | PIC X(4096) | No | each Call | |
In | MDTEST-ACT-CHAR | PIC X(4096) | No | each Call | |
In | MDTEST-IGNORE-CASE | PIC 1 | Yes | first only | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
MDTest_Char_NotEqual
checks if "Expected Value" & "Actual Value" contain different values
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Expected Value | VarChar(4096) | Value | |
In | Actual Value | VarChar(4096) | Value | |
In | Ignore Case | Ind | Const, NoPass, Omit | Case Insensitive On/Off |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-CHAR-NOTEQUAL USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-EXP-CHAR | PIC X(4096) | No | each Call | |
In | MDTEST-ACT-CHAR | PIC X(4096) | No | each Call | |
In | MDTEST-IGNORE-CASE | PIC 1 | Yes | first only | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
MDTest_Char_Contains
checks if "Actual Value" contains "Expected Value"
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Expected Value | VarChar(4096) | Value | |
In | Actual Value | VarChar(4096) | Value | |
In | Ignore Case | Ind | Const, NoPass, Omit | Case Insensitive On/Off |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-CHAR-CONTAINS USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-EXP-CHAR | PIC X(4096) | No | each Call | |
In | MDTEST-ACT-CHAR | PIC X(4096) | No | each Call | |
In | MDTEST-IGNORE-CASE | PIC 1 | Yes | first only | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
MDTest_Char_NotContains
checks if "Actual Value" does not contain "Expected Value"
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Expected Value | VarChar(4096) | Value | |
In | Actual Value | VarChar(4096) | Value | |
In | Ignore Case | Ind | Const, NoPass, Omit | Case Insensitive On/Off |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-CHAR-NOTCONTAINS USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-EXP-CHAR | PIC X(4096) | No | each Call | |
In | MDTEST-ACT-CHAR | PIC X(4096) | No | each Call | |
In | MDTEST-IGNORE-CASE | PIC 1 | Yes | first only | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
Dcl-S h_Result Like(MDTest_Char_NotContains);
h_Result = MDTest_Char_NotContains('test':'MDTest':*On);
MDTest_Char_StartsWith
checks if "Actual Value" starts with value of "Expected Value"
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Expected Value | VarChar(4096) | Value | |
In | Actual Value | VarChar(4096) | Value | |
In | Ignore Case | Ind | Const, NoPass, Omit | Case Insensitive On/Off |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-CHAR-STARTSWITH USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-EXP-CHAR | PIC X(4096) | No | each Call | |
In | MDTEST-ACT-CHAR | PIC X(4096) | No | each Call | |
In | MDTEST-IGNORE-CASE | PIC 1 | Yes | first only | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
MDTest_Char_EndsWith
checks if "Actual Value" ends with value of "Expected Value"
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Expected Value | VarChar(4096) | Value | |
In | Actual Value | VarChar(4096) | Value | |
In | Ignore Case | Ind | Const, NoPass, Omit | Case Insensitive On/Off |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-CHAR-ENDSWITH USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-EXP-CHAR | PIC X(4096) | No | each Call | |
In | MDTEST-ACT-CHAR | PIC X(4096) | No | each Call | |
In | MDTEST-IGNORE-CASE | PIC 1 | Yes | first only | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
MDTest_Char_Blank
checks if "Actual Value" is empty
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Actual Value | VarChar(4096) | Value | |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-CHAR-BLANK USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-ACT-CHAR | PIC X(4096) | No | each Call | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
Dcl-S h_Result Like(MDTest_Char_Blank);
Dcl-S h_Name Char(10) Inz('Sam');
h_Result = MDTest_Char_Blank(h_Name);
MDTest_Char_NotBlank
checks if "Actual Value" is not empty
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Actual Value | VarChar(4096) | Value | |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-CHAR-NOTBLANK USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-ACT-CHAR | PIC X(4096) | No | each Call | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
Dcl-S h_Result Like(MDTest_Char_NotBlank);
Dcl-S h_Name Char(10) Inz('Sam');
h_Result = MDTest_Char_NotBlank(h_Name);
MDTest_Char_In
checks if "Actual Value" is found in "Elements"
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Actual Value | VarChar(256) | Value | |
In | Number of Elements | Int(10) | Value | |
In | Elements | VarChar(256) | Dim(50), Value | |
In | Ignore Case | Ind | Const, NoPass, Omit | Case Insensitive On/Off |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-CHAR-IN USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-CHAR-ELEM | PIC X(256) | No | each Call | |
In | MDTEST-CARRAY-COUNT | PIC S9(9) COMP-4 | No | first only | |
In | MDTEST-CHAR-ARRAY | PIC X(256) | No | first only | |
In | MDTEST-IGNORE-CASE | PIC 1 | Yes | first only | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
Dcl-S h_Result Like(MDTest_Char_In);
Dcl-S h_Elements VarChar(256) Dim(50);
h_Elements(1) = 'ABC';
h_Elements(2) = 'DEF';
h_Result = MDTest_Char_In('def':2:h_Elements:*On);
MDTest_Char_NotIn
checks if "Actual Value" is not found in "Elements"
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Actual Value | VarChar(256) | Value | |
In | Number of Elements | Int(10) | Value | |
In | Elements | VarChar(256) | Dim(50), Value | |
In | Ignore Case | Ind | Const, NoPass, Omit | Case Insensitive On/Off |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-CHAR-NOTIN USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-CHAR-ELEM | PIC X(256) | No | each Call | |
In | MDTEST-CARRAY-COUNT | PIC S9(9) COMP-4 | No | first only | |
In | MDTEST-CHAR-ARRAY | PIC X(256) | No | first only | |
In | MDTEST-IGNORE-CASE | PIC 1 | Yes | first only | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Exampleregex
Dcl-S h_Result Like(MDTest_Char_NotIn);
Dcl-S h_Elements VarChar(256) Dim(50);
h_Elements(1) = 'ABC';
h_Elements(2) = 'DEF';
h_Result = MDTest_Char_NotIn('def':2:h_Elements:*On);
MDTest_Char_RegEx
checks if Regular Expression in "Expected Values" is found in "Actual Value"
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Expected Value | VarChar(4096) | Value | |
In | Actual Value | VarChar(4096) | Value | |
In | Ignore Case | Ind | Const, NoPass, Omit | Case Insensitive On/Off |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-CHAR-REGEX USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-EXP-CHAR | PIC X(4096) | No | each Call | |
In | MDTEST-ACT-CHAR | PIC X(4096) | No | each Call | |
In | MDTEST-IGNORE-CASE | PIC 1 | Yes | first only | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
h_Status = MDTest_Char_Regex('^(?:\w+\.?)*\w+@(?:\w+\.)*\w+$':'Saman.Neinawaie@MidrangeDynamics.com');
MDTest_Char_NotRegEx
checks if Regular Expression in "Expected Values" is not found in "Actual Value"
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Expected Value | VarChar(4096) | Value | |
In | Actual Value | VarChar(4096) | Value | |
In | Ignore Case | Ind | Const, NoPass, Omit | Case Insensitive On/Off |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-CHAR-NOTREGEX USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-EXP-CHAR | PIC X(4096) | No | each Call | |
In | MDTEST-ACT-CHAR | PIC X(4096) | No | each Call | |
In | MDTEST-IGNORE-CASE | PIC 1 | Yes | first only | |
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |
RPG Example
h_Status = MDTest_Char_NoRegex('^(?:\w+\.?)*\w+@(?:\w+\.)*\w+$':'Saman.Neinawaie@MidrangeDynamics.com');
Code Coverage Functions
MDTest_reg_CodeCov_Mod
register code coverage for a module
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Program Library | Char(10) | Value | Library Name, *LIBL, *CURLIB |
In | Program Name | Char(10) | Value | |
In | Module | Char(10) | Value | |
In | Program Type | Char(10) | Value | *PGM, *SRVPGM |
In | min. % | Int(10) | Const, NoPass, Omit | |
In | max. % | Int(10) | Const, NoPass, Omit | |
In | min. Hit Lines | Int(10) | Const, NoPass, Omit | |
In | max. Hit Lines | Int(10) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-REG-CODECOV-MOD USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-PGM-LIB | PIC X(10) | No | first only | |
In | MDTEST-PGM-NAME | PIC X(10) | No | first only | |
In | MDTEST-PGM-MODULE | PIC X(10) | No | first only | |
In | MDTEST-PGM-TYPE | PIC X(10) | No | first only | *PGM, *SRVPGM |
In | MDTEST-MIN-PERCENTAGE | PIC S9(9) COMP-5 | Yes | each Call | |
In | MDTEST-MAX-PERCENTAGE | PIC S9(9) COMP-5 | Yes | each Call | |
In | MDTEST-MIN-LINES-HIT | PIC S9(9) COMP-5 | Yes | each Call | |
In | MDTEST-MAX-LINES-HIT | PIC S9(9) COMP-5 | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only | |
##### RPG Example | |||||
MDTest_rpt_CodeCov
generate code coverage report
ILE Procedure Interface
Direction | Field | Type | Options | Comment |
---|---|---|---|---|
Out | Status | Char(10) | MDTest_FAIL or MDTest_PASS | |
In | Message | VarChar(128) | Const, NoPass, Omit | |
In | Report Group | Char(10) | Const, NoPass, Omit |
COBOL SECTION
MDTEST-RPT-CODECOV USING
Direction | Field | Type | Optional | Initialized | Comment |
---|---|---|---|---|---|
Out | MDTEST-STATUS | PIC X(10) | MDTEST-FAIL or MDTEST-PASS | ||
In | MDTEST-MSG | PIC X(128) | Yes | each Call | |
In | MDTEST-REPORT-GROUP | PIC X(10) | Yes | first only |