Skip to main content

Say, I have a copybook 'CPBK' which is placed in MYFOLDER.

CPBK:
   03  WA-FIELD1   PIC X.
   03  WA-FIELD2   PIC S9(9) BINARY.
   03  WA-FIELD3   PIC 9(3).

 
So when I access copybook in my program I use following statement

in Working Storage Section.

COPY  CPBK in MYFOLDER.

 

Now, I have a table having following fields

TABL :
FIELD_1    CHAR (1),
FIELD_2    NUMBER (9),
FIELD_3    CHAR (3)


I want to perform 'Select *  from TABL' and fetch the details in

copybook CPBK

But I get compilation error when trying to declare following:
 EXEC SQL BEGIN DECLARE SECTION END-EXEC.
 01 CPBKREC.
    COPY  CPBK  IN MYFOLDER.
 EXEC SQL END DECLARE SECTION END-EXEC.

and for fetch -   FETCH INTO : CPBKREC


Getting following compilation error-

                     INTO : CPBKREC
.................................1
PCB-S-00208, Incorrect type for host variable "CPBKREC"

 

Can anyone please help resolving this.

Say, I have a copybook 'CPBK' which is placed in MYFOLDER.

CPBK:
   03  WA-FIELD1   PIC X.
   03  WA-FIELD2   PIC S9(9) BINARY.
   03  WA-FIELD3   PIC 9(3).

 
So when I access copybook in my program I use following statement

in Working Storage Section.

COPY  CPBK in MYFOLDER.

 

Now, I have a table having following fields

TABL :
FIELD_1    CHAR (1),
FIELD_2    NUMBER (9),
FIELD_3    CHAR (3)


I want to perform 'Select *  from TABL' and fetch the details in

copybook CPBK

But I get compilation error when trying to declare following:
 EXEC SQL BEGIN DECLARE SECTION END-EXEC.
 01 CPBKREC.
    COPY  CPBK  IN MYFOLDER.
 EXEC SQL END DECLARE SECTION END-EXEC.

and for fetch -   FETCH INTO : CPBKREC


Getting following compilation error-

                     INTO : CPBKREC
.................................1
PCB-S-00208, Incorrect type for host variable "CPBKREC"

 

Can anyone please help resolving this.

What MF product and version are you using and what version of Pro*COBOL?

I tested here with NX 5.1 and Pro*COBOL from Oracle 11 and it worked fine.

file CPBK (with or without extension .cpy) resides in folder called MYFOLDER off of the project folder. Is MYFOLDER the actual name of the folder you are using or are you using an environment variable, etc.?

CPBK contains:

       01 CPBKREC.
          03  WA-FIELD1   PIC X.
          03  WA-FIELD2   PIC S9(9) BINARY.
          03  WA-FIELD3   PIC 9(3).

And the following is the program I used.

       IDENTIFICATION DIVISION.
       PROGRAM-ID.  ORACONNECT.
       ENVIRONMENT DIVISION.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
           exec sql include sqlca end-exec

           EXEC SQL BEGIN DECLARE SECTION END-EXEC.

       01  USERNAME  PIC X(5).
       01  PASSWD    PIC X(6).

       copy CPBK in MYFOLDER.

           EXEC SQL END DECLARE SECTION END-EXEC.
       01 pp procedure-pointer.
       procedure division.

            set pp to entry "ORASQL11"
            MOVE "SCOTT" TO USERNAME.
            MOVE "tiger2" TO PASSWD.
            EXEC SQL
                CONNECT :USERNAME IDENTIFIED BY :PASSWD
            END-EXEC.
            if sqlcode not = 0
               display "connect error " sqlcode
            end-if
            exec sql declare mycursor cursor for
               select * from TABL
            end-exec
            display sqlcode
            exec sql open mycursor end-exec
            exec sql fetch mycursor into :CPBKREC end-exec
            display sqlcode
            goback.



Say, I have a copybook 'CPBK' which is placed in MYFOLDER.

CPBK:
   03  WA-FIELD1   PIC X.
   03  WA-FIELD2   PIC S9(9) BINARY.
   03  WA-FIELD3   PIC 9(3).

 
So when I access copybook in my program I use following statement

in Working Storage Section.

COPY  CPBK in MYFOLDER.

 

Now, I have a table having following fields

TABL :
FIELD_1    CHAR (1),
FIELD_2    NUMBER (9),
FIELD_3    CHAR (3)


I want to perform 'Select *  from TABL' and fetch the details in

copybook CPBK

But I get compilation error when trying to declare following:
 EXEC SQL BEGIN DECLARE SECTION END-EXEC.
 01 CPBKREC.
    COPY  CPBK  IN MYFOLDER.
 EXEC SQL END DECLARE SECTION END-EXEC.

and for fetch -   FETCH INTO : CPBKREC


Getting following compilation error-

                     INTO : CPBKREC
.................................1
PCB-S-00208, Incorrect type for host variable "CPBKREC"

 

Can anyone please help resolving this.

Hi Chris,

I am working with :
Cobol v5.1.00
Oracle 12.1.0.1.0


MYFOLDER is folder where we store copybooks

Say, I have a copybook 'CPBK' which is placed in MYFOLDER.

CPBK:
   03  WA-FIELD1   PIC X.
   03  WA-FIELD2   PIC S9(9) BINARY.
   03  WA-FIELD3   PIC 9(3).

 
So when I access copybook in my program I use following statement

in Working Storage Section.

COPY  CPBK in MYFOLDER.

 

Now, I have a table having following fields

TABL :
FIELD_1    CHAR (1),
FIELD_2    NUMBER (9),
FIELD_3    CHAR (3)


I want to perform 'Select *  from TABL' and fetch the details in

copybook CPBK

But I get compilation error when trying to declare following:
 EXEC SQL BEGIN DECLARE SECTION END-EXEC.
 01 CPBKREC.
    COPY  CPBK  IN MYFOLDER.
 EXEC SQL END DECLARE SECTION END-EXEC.

and for fetch -   FETCH INTO : CPBKREC


Getting following compilation error-

                     INTO : CPBKREC
.................................1
PCB-S-00208, Incorrect type for host variable "CPBKREC"

 

Can anyone please help resolving this.

Hi Chris,

I am working with :
Cobol v5.1.00
Oracle 12.1.0.1.0


MYFOLDER is folder where we store copybooks

Say, I have a copybook 'CPBK' which is placed in MYFOLDER.

CPBK:
   03  WA-FIELD1   PIC X.
   03  WA-FIELD2   PIC S9(9) BINARY.
   03  WA-FIELD3   PIC 9(3).

 
So when I access copybook in my program I use following statement

in Working Storage Section.

COPY  CPBK in MYFOLDER.

 

Now, I have a table having following fields

TABL :
FIELD_1    CHAR (1),
FIELD_2    NUMBER (9),
FIELD_3    CHAR (3)


I want to perform 'Select *  from TABL' and fetch the details in

copybook CPBK

But I get compilation error when trying to declare following:
 EXEC SQL BEGIN DECLARE SECTION END-EXEC.
 01 CPBKREC.
    COPY  CPBK  IN MYFOLDER.
 EXEC SQL END DECLARE SECTION END-EXEC.

and for fetch -   FETCH INTO : CPBKREC


Getting following compilation error-

                     INTO : CPBKREC
.................................1
PCB-S-00208, Incorrect type for host variable "CPBKREC"

 

Can anyone please help resolving this.

Are you using the Oracle Pro*COBOL pre-compiler or OpenESQL with a target of Oracle?

Perhaps you need to SQL INCLUDE the copybook for it to be processed by the Oracle Pro*COBOL pre-compiler.

EXEC SQL BEGIN DECLARE SECTION END-EXEC.
01 CPBKREC.
EXEC SQL INCLUDE CPBK END-EXEC.
EXEC SQL END DECLARE SECTION END-EXEC.

You may be able to stack the CP copybook pre-compiler before the Pro*COBOL pre-compiler to expand the copybooks before the SQL pre-compiler processes of the code allowing you to continue using the IN MYFOLDER on the copy statement.

To stack the CP pre-processor before the Pro*COBOL pre-processor use directives similar to this:
p(cobsql) CSQLT=ORACLE CST CSP DIS MAKESYN SQLDEBUG VERBOSE KEEPCBL END-C p(cp) LIMITED-SEARCH ENDP ENDP

You could tell the compiler which folder(s) the copybooks reside in using the COBCPY environment variable precluding the use of IN MYFOLDER too.

Say, I have a copybook 'CPBK' which is placed in MYFOLDER.

CPBK:
   03  WA-FIELD1   PIC X.
   03  WA-FIELD2   PIC S9(9) BINARY.
   03  WA-FIELD3   PIC 9(3).

 
So when I access copybook in my program I use following statement

in Working Storage Section.

COPY  CPBK in MYFOLDER.

 

Now, I have a table having following fields

TABL :
FIELD_1    CHAR (1),
FIELD_2    NUMBER (9),
FIELD_3    CHAR (3)


I want to perform 'Select *  from TABL' and fetch the details in

copybook CPBK

But I get compilation error when trying to declare following:
 EXEC SQL BEGIN DECLARE SECTION END-EXEC.
 01 CPBKREC.
    COPY  CPBK  IN MYFOLDER.
 EXEC SQL END DECLARE SECTION END-EXEC.

and for fetch -   FETCH INTO : CPBKREC


Getting following compilation error-

                     INTO : CPBKREC
.................................1
PCB-S-00208, Incorrect type for host variable "CPBKREC"

 

Can anyone please help resolving this.

Thanks Morgan.
Will try to stack copybook pre-compiler before Pro*Cobol and then check.