Top
NetCOBOL V11.0 NetCOBOL Studio User's Guide
FUJITSU Software

11.5.2 Notes

This section provides notes on developing CORBA server applications.

11.5.2.1 Usable Data Types

The table below lists CORBA data types and their corresponding data types in other languages.
For details on data types that can be defined, refer to the "Interstage Studio User's Guide".

Table 11.18 COBOL (object-oriented COBOL) mapping

CORBA type

COBOL (object-oriented COBOL) mapping type

COBOL native type

long

CORBA-long

PIC S9(9) COMP-5

unsigned long

CORBA-unsigned-long

PIC 9(9) COMP-5

short

CORBA-short

PIC S9(4) COMP-5

unsigned short

CORBA-unsigned-short

PIC 9(4) COMP-5

long long

CORBA-long-long

PIC S9(18) COMP-5

unsigned long long

CORBA-unsigned-long-long

PIC 9(18) COMP-5

float

CORBA-float

COMP-1

double

CORBA-double

COMP-2

char

CORBA-char

PIC X

wchar

CORBA-wchar

PIC N

octet

CORBA-octet

PIC X

boolean

CORBA-boolean

PIC 1(1)

fixed <m+n,n>

Cannot be used

PIC S9 (m+n,n) PACKED-DECIMAL

string (fixed length)

PIC X(n)

PIC X(n)

string (variable length)

Cannot be used

Cannot be used

wstring (fixed length)

PIC N(n)

PIC N(n)

wstring (variable length)

Cannot be used

Cannot be used

enum

CORBA-enum

PIC 9(10) COMP-5

any

Cannot be used

Cannot be used

Structure (fixed length)

Group item

Group item

Structure (variable length)

Class

Class

Union

Class

Class

sequence type (fixed length)

Class

Class

sequence type (variable length)

Class

Class

array type

Cannot be used

Cannot be used

The CORBA server application generation wizard does not support the data types listed below. To use these data types, create templates and modify the relevant IDL file and program source according to the "Interstage Application Server Distributed Application Development Guide (CORBA Service Edition)".

11.5.2.2 Operation of Iteration Items

Iteration items are mapped to the sequence type as described below.

Table 11.19 Iteration item mapping

Number of dimensions

Object-oriented COBOL

1

sequence type (fixed length)

2 to 5

Cannot be used

Mapping a iteration definition to the IDL file

Mapping of an iteration definition to the IDL file is explained below.

Mapping one-dimensional items to the sequence type

One-dimensional items are mapped to the sequence type.

For object-oriented COBOL

The following example shows mapping with a 4-byte integer specified for the data type, "a" for the type name, and 10 for the iteration count.

    typedef sequence<long, 10> a ;

Operation of iteration items

Operation of iteration items is explained below.

One dimension (object-oriented COBOL)

Operation of iteration items is shown below. When the following IDL file is compiled, the sequence type is mapped to a sequence class.

IDL file

module ODsample {
      typedef sequence<long,10> sampleseq;
      interface seqtest {
               sampleseq op1(in sampleseq param1,
                        out sampleseq param2,
                        inout sampleseq param3);
      };
};

The factory method, object methods, and properties of the sequence class are listed below.

Table 11.20 Sequence class

Category

Method/property name

Function

Factory method

NEW-WITH-LENGTH

Creates a sequence class of the specified length

Object method

GET-VALUE

Obtains the value of the element of the specified number

SET-VALUE

Sets a value for the element of the specified number

CLONE

Makes a copy of a sequence class

Property

SEQ-MAXIMUM

Gets the value of the maximum sequence length

SEQ-LENGTH

Gets or sets the sequence length value

Example of using iteration items

 METHOD-ID. OP1 AS "OP1" OVERRIDE.
* <IDL-INFO-START>
* sampleseq op1(in sampleseq param1,out sampleseq param2,inout sampleseq param3)
* <IDL-INFO-END>
 DATA DIVISION.
 WORKING-STORAGE SECTION.
 01 SEQ-VALUE TYPE  CORBA-LONG.
 01 I         TYPE  CORBA-UNSIGNED-LONG.

 LINKAGE SECTION.
 01 RETURN-VALUE  TYPE ODSAMPLE-SAMPLESEQ.
 01 PARAM1  TYPE ODSAMPLE-SAMPLESEQ.
 01 PARAM2  TYPE ODSAMPLE-SAMPLESEQ.
 01 PARAM3  TYPE ODSAMPLE-SAMPLESEQ.
 PROCEDURE DIVISION
         USING 
                   PARAM1
                   PARAM2
                   PARAM3
         RETURNING RETURN-VALUE 
                   .

*  IN PARAMETER
     PERFORM VARYING I FROM 1 BY 1 UNTIL I > 10
       INVOKE PARAM1 "GET-VALUE" USING I RETURNING SEQ-VALUE
     END-PERFORM.
     
*  OUT PARAMETER
     INVOKE SEQUENCE-LONG-10 "NEW" RETURNING PARAM2.
     MOVE 10 TO SEQ-LENGTH OF PARAM2.
     PERFORM VARYING I FROM 1 BY 1 UNTIL I > 10
       COMPUTE SEQ-VALUE = I * 100
       INVOKE PARAM2 "SET-VALUE" USING I SEQ-VALUE
     END-PERFORM.

*  INOUT PARAMETER
     PERFORM VARYING I FROM 1 BY 1 UNTIL I > 10
       INVOKE PARAM3 "GET-VALUE" USING I RETURNING SEQ-VALUE
       COMPUTE SEQ-VALUE = SEQ-VALUE * 100
       INVOKE PARAM3 "SET-VALUE" USING I SEQ-VALUE
     END-PERFORM.

*  RESULT
     INVOKE SEQUENCE-LONG-10 "NEW" RETURNING RETURN-VALUE.
     MOVE 10 TO SEQ-LENGTH OF RETURN-VALUE.
     PERFORM VARYING I FROM 1 BY 1 UNTIL I > 10
       COMPUTE SEQ-VALUE = I * 10000
       INVOKE RETURN-VALUE "SET-VALUE" USING I SEQ-VALUE
     END-PERFORM.
                   
 END METHOD OP1.

Point

As for the sequence type, in cases where the mode is "in" or "inout", a data area already exists on the calling side and need not be allocated. However, in cases of "out" mode or the return value, the server application must allocate a data area.

11.5.2.3 Operating Structures

Structures are mapped to group items as described below.

Table 11.21 Structure mapping

Type

Object-oriented COBOL

Structure (fixed length)

Group item

Structure (variable length)

Cannot be used

An example of using structures when the following IDL file is compiled, is shown below.

IDL file
module ODsample {
      struct samplestruct {
               long item1;
               long item2;
      };
      interface structtest {
               samplestruct op1(in samplestruct param1,
                         out samplestruct param2,
                         inout samplestruct param3);
      };
};
Example of structure items
 METHOD-ID. OP1 AS "OP1" OVERRIDE.
* <IDL-INFO-START>
* samplestruct op1(in samplestruct param1,out samplestruct param2,inout samplestruct param3)
* <IDL-INFO-END>
 DATA DIVISION.
 WORKING-STORAGE SECTION.
 LINKAGE SECTION.
 01 RETURN-VALUE TYPE ODSAMPLE-SAMPLESTRUCT.
 01 PARAM1 TYPE ODSAMPLE-SAMPLESTRUCT.
 01 PARAM2 TYPE ODSAMPLE-SAMPLESTRUCT.
 01 PARAM3 TYPE ODSAMPLE-SAMPLESTRUCT.
 PROCEDURE DIVISION
         USING 
                   PARAM1
                   PARAM2
                   PARAM3
         RETURNING RETURN-VALUE 
                   .

*  IN PARAMETER
*  OUT PARAMETER
*  INOUT PARAMETER
     MOVE ITEM1 OF PARAM1 TO ITEM1 OF PARAM2.
     MOVE ITEM2 OF PARAM3 TO ITEM2 OF PARAM2.

     MOVE 2 TO ITEM1 OF PARAM3.
     MOVE 3 TO ITEM2 OF PARAM3.

*  RESULT
     MOVE 4 TO ITEM1 OF RETURN-VALUE.
     MOVE 5 TO ITEM2 OF RETURN-VALUE.
      
 END METHOD OP1.

11.5.2.4 Inheritance

The IDL generator can generate neither inheritance code nor #include statements.
To inherit a module or interface, edit the IDL file, using an editor to add coding of the inherited part.

11.5.2.5 Multi-instance System

For a program to be operated on multi-instance system, it is mandatory that the ORB initialization part of the program is modified.
For details about the multi-instance system and ORB initialization method, refer to the "Interstage Application Server Distributed Application Development Guide (CORBA Service Edition)" and "Interstage Application Server Reference Manual (Command Edition)".

11.5.2.6 Database Access

Following are two methods for creating the CORBA server application that performs database access .

For details and notes about the database access method (ESQL/COBOL etc.) provided by NetCOBOL, refer to "NetCOBOL Users' Guide" and "NetCOBOL Software Instructions".