You can embed Java source within your COBOL program with the EXEC JAVA ... END-EXEC statement. Java source is generated at the point in which it appears within the program.
Reference COBOL variables with the ::element-or-group-name:: designator. If used on the right side of an assignment statement or within a method call, this designator will generate accessor method invocations (getters) for the various types. For example, if the element is defined as a PIC X(10) the designator will replaced by an accessor that returns a String value for the element. An element defined as a PIC 9(9) COMP would produce an int value. For example,
EXEC JAVA
String a = ::WS-PICX10::;
System.out.println("value: " + a);
END-EXEC
You can invoke mutilator methods (setters) by placing a "." and method name and parameters after the designator. For example,
EXEC JAVA
::WS-DATE::.move((new Date()).toString());
END-EXEC
All of the Variable class accessors and mutilators that are part of the ICobol interrface are available to use. Here are some examples,
Datatype | Accessor | Mutilator |
any | nothing | move(variable) |
byte | toByteArray() | fromByteArray(variable) |
int | toInt() | fromInt(variable) |
float | toFloat() | fromFloat(variable) |
double | toDouble() | fromDouble(variable) |
Your Java should be fairly simple, prefering to invoke other pure Java class methods you define within the java_source folder of your COBOL project. To import these methods into the generated Java source, or other classes, use the compiler directive -out:importjava followed by a class specification. One ore more of these directives can be provided. These can be included in the source file with the $SET DIRECTIVE statement.
Here's a complete example:
$SET DIRECTIVE(-out:importjava org.json.*)
IDENTIFICATION DIVISION.
PROGRAM-ID. json2cobol.
*
* how to use JSON in Elastic COBOL
*
WORKING-STORAGE SECTION.
01 WS-PAGENAME PIC X(20) VALUE SPACES.
01 PARM-DATA PIC X(100) VALUE SPACES.
PROCEDURE DIVISION.
move '{"pageInfo": {"pageName": "abc","pagePic": "http://exa -
'mple.com/content.jpg"}}' to parm-data
display 'JSON to Parse:' parm-data upon sysout.
exec java
JSONObject obj = new JSONObject(::PARM-DATA::);
JSONObject pageInfoObj = obj.getJSONObject("pageInfo");
String pageName = pageInfoObj.getString("pageName");
::WS-PAGENAME::.move(pageName);
end-exec.
display 'Parsed JSON page name: ' WS-PAGENAME upon sysout.
end program json2cobol.
Compile and run program with the -cp flag to indicate where to find the JSON jar files (CLASSPATH contains ecobol.jar)
ecobol -cp $CLASSPATH:json.jar json2cobol.cbl
java -cp $CLASSPATH:json.jar json2cobol
0 Comments