RAISE
General Format
RAISE Exception-Class
Syntax Rules
1. In a PROGRAM-ID program, Exception-Class is a java.lang.RuntimeException class or any known subclass.
2. In a CLASS-ID program, Exception-Class is a java.lang.Exception class or any known subclass. If Exception-Class is a superclass of java.lang.RuntimException, then the method in which the RAISE statement is used, must specify Exception-Class in the RAISING clause of the PROCEDURE DIVISION.
Note - if the above rules are not respected, a incompilable Java source may be generated by the isCOBOL Compiler.
General Rules
1. If caught, the EXCEPTION-OBJECT will be set to the instance of the Exception-Class
Examples
Perform three jobs in sequence and stop at the first one that fails.
 program-id. threeJobs.
 configuration section.
 repository.
    class runex as "java.lang.RuntimeException".
 working-storage section.
 77 elab-status pic 9.
    88 ok       value 1.
    88 failed   value 0.
 procedure division.
 MAIN.
    try 
       perform JOB-1
       perform JOB-2
       perform JOB-3
       display "All jobs completed successfully!"
    catch exception
       display exception-object:>getMessage()
    end-try.
    goback.
 JOB-1. 
*>  job logic here
    if failed
       raise runex:>new("Job 1: failed")
    end-if.
 JOB-2.
*>  job logic here 
    if failed
       raise runex:>new("Job 2: failed")
    end-if.
 JOB-3.
*>  job logic here 
    if failed
       raise runex:>new("Job 3: failed")
    end-if.
Invoke a CLASS-ID that may return a custom exception named BadParamException:
BadParamException.cbl
 identification division.
 class-id. BadParamException as "BadParamException" inherits JException.
 configuration section.
 repository.
 class JException as "java.lang.Exception"
 class JString as "java.lang.String".
 identification division.
 object.
 procedure division.
 identification division.
 method-id. new as "new".
 procedure division.
 main.
     super:>new()
 end method.
 identification division.
 method-id. new as "new".
 linkage section.
     77 lk-message object reference JString.
 procedure division using lk-message.
 main.
     super:>new(lk-message)
 end method.
 end object.
StrProcessor.cbl
 identification division.
 class-id. StrProcessor as "StrProcessor".
 configuration section.
 repository.
 class myEx as "BadParamException"
 class JString as "java.lang.String".
 identification division.
 factory.
 procedure division.
 identification division.
 method-id. processString as "processString".
 working-storage section.
 77 wk-str pic x any length.
 77 i pic 99.
 linkage section.
 77 lk-str object reference JString.
 procedure division using lk-str raising myEx.
 main.
     set wk-str to lk-str.
*> string must be at least 5 characters in size
     if function length(wk-str) < 5
        raise myEx:>new("string is less than 5 characters in size")
     end-if.
*> string must not contain spaces
     initialize i.
     inspect wk-str tallying i for all spaces
     if i > 0
        raise myEx:>new("string includes spaces")
     end-if.
*> go ahead processing the string
 end method.
 end factory.
PROG.cbl
 program-id. prog.
 configuration section.
 repository.
 class sp as "StrProcessor".
 procedure division.
 main.
     try
        sp:>processString("X Y Z")
 *>the above statement will raise a BadParamException as the string includes spaces
     catch exception
        exception-object:>printStackTrace()
     end-try.
     goback.