Home » Developer & Programmer » Precompilers, OCI & OCCI » Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column
Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653905] Thu, 21 July 2016 22:52 Go to next message
hui shen
Messages: 15
Registered: July 2016
Junior Member
Hi experts
I am using procob dynamic sql to execute a sql query statement, but i could not find a way to get real data length value of a VARCHAR2 column.
For example:
CREATE TABLE TESTAB(CCC VARCHAR2(10));
INSERT INTO TESTAAB VALUES('1234');

Currently, the procob dynamic sql ("SELECT * FROM TESTTAB")can let me retrieve the column metadata information, e.g., column name ("CCC"), column datatype("VARCHAR2"), and max column length (10);
and can also fetch out the data ("1234"), but i could not find a way to get the data length.

1. define SELDSC
01 SELDSC.
02 SQLDNUM PIC S9(9) COMP-5 VALUE 20.
02 SQLDFND PIC S9(9) COMP-5.
02 SELDVAR OCCURS 20 TIMES.
03 SELDV PIC S9(18) COMP-5.
03 SELDFMT PIC S9(18) COMP-5.
03 SELDVLN PIC S9(9) COMP-5.
03 SELDFMTL PIC S9(4) COMP-5.
03 SELDVTYP PIC S9(4) COMP-5.
03 SELDI PIC S9(18) COMP-5.
03 SELDH-VNAME PIC S9(18) COMP-5.
03 SELDH-MAX-VNAMEL PIC S9(4) COMP-5.
03 SELDH-CUR-VNAMEL PIC S9(4) COMP-5.
03 SELDFILL1 PIC S9(9) COMP-5.
03 SELDI-VNAME PIC S9(18) COMP-5.
03 SELDI-MAX-VNAMEL PIC S9(4) COMP-5.
03 SELDI-CUR-VNAMEL PIC S9(4) COMP-5.
03 SELDFILL2 PIC S9(9) COMP-5.
03 SELDFCLP PIC S9(18) COMP-5.
03 SELDFCRCP PIC S9(18) COMP-5.
01 XSELDI.
03 SEL-DI OCCURS 20 TIMES PIC S9(4) COMP-5.
01 XSELDIVNAME.
03 SEL-DI-VNAME OCCURS 20 TIMES PIC X(80).
01 XSELDV.
03 SEL-DV OCCURS 20 TIMES PIC X(80).
01 XSELDHVNAME.
03 SEL-DH-VNAME OCCURS 20 TIMES PIC X(80).
2. bind buffer
CALL "SQLADR" USING SEL-DV(COLUMN-INDEX) SELDV(COLUMN-INDEX).
MOVE "SELECT * FROM TESTTAB" TO DYN-STATEMENT.
EXEC SQL PREPARE S1 FROM :DYN-STATEMENT END-EXEC.
EXEC SQL DECLARE C1 CURSOR FOR S1 END-EXEC.
EXEC SQL OPEN C1 END-EXEC.
EXEC SQL DESCRIBE SELECT LIST FOR S1 INTO SELDSC END-EXEC.

3. fetch data row
EXEC SQL FETCH C1 USING DESCRIPTOR SELDSC END-EXEC.
4. finally
buffer SEL-DV was filled with "ABCD ", there is 6-spaced appended. there is no way to get the real data length(in this case, it's 4).
Because i cannot distinguish whether the append white space is part of data content or not.

Thanks.
Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653910 is a reply to message #653905] Fri, 22 July 2016 01:32 Go to previous messageGo to next message
Michel Cadot
Messages: 68624
Registered: March 2007
Location: Nanterre, France, http://...
Senior Member
Account Moderator

Return LENGTH(CCC)?

Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653912 is a reply to message #653910] Fri, 22 July 2016 01:46 Go to previous messageGo to next message
hui shen
Messages: 15
Registered: July 2016
Junior Member
Hi Michel,
I did not get your point, do you mean use "SELECT LENGTH(CCC) FROM TESTTAB" ?
The dynamic SQL is coming from user input at runtime, like "SELECT CCC FROM TESTTAB", or "SELECT * FROM TESTTAB"; at that time program don't know the SQL details, so I using dynamic SQL to implement this function.
Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653915 is a reply to message #653912] Fri, 22 July 2016 01:57 Go to previous messageGo to next message
Michel Cadot
Messages: 68624
Registered: March 2007
Location: Nanterre, France, http://...
Senior Member
Account Moderator

There are 2 things I don't understand:
* why have you added spaces at the end of your data
* why do you need the length

Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653917 is a reply to message #653915] Fri, 22 July 2016 02:14 Go to previous messageGo to next message
hui shen
Messages: 15
Registered: July 2016
Junior Member

> * why have you added spaces at the end of your data
This is the problem i am asking for help; the buffer is defined with max length, suppose "PIC X(80)".
The real data length can be 0, 1, 2, ...
It's the procob/COBOL API that append the white-space to the buffer; COBOL doesn't end a string using '\0'; instead procob/cobol write the real data into left-side of buffer, and append the rest with white space.
I want to know the real data length.

> * why do you need the length
This is common requirement, the data column is variable length (VARCHAR2); i want to read the real data value (discard the appended white), and maybe write back to other database/textfile/service/etc.
Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653918 is a reply to message #653917] Fri, 22 July 2016 02:20 Go to previous messageGo to next message
Michel Cadot
Messages: 68624
Registered: March 2007
Location: Nanterre, France, http://...
Senior Member
Account Moderator

Couldn't you just right trim the spaces?

Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653919 is a reply to message #653918] Fri, 22 July 2016 02:23 Go to previous messageGo to next message
hui shen
Messages: 15
Registered: July 2016
Junior Member
i am afraid i could not; because i could not tell the difference whether the right-side white space is part of data content, or just appended.
(Now fewer and fewer people are using COBOL, i searched a lot, but did not get much)
Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653921 is a reply to message #653919] Fri, 22 July 2016 02:30 Go to previous messageGo to next message
Michel Cadot
Messages: 68624
Registered: March 2007
Location: Nanterre, France, http://...
Senior Member
Account Moderator

So your only way is to change the program to use a VARCHAR variable which will give you the length.

[Edit: missing letter]

[Updated on: Fri, 22 July 2016 02:47]

Report message to a moderator

Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653923 is a reply to message #653921] Fri, 22 July 2016 02:40 Go to previous messageGo to next message
hui shen
Messages: 15
Registered: July 2016
Junior Member
anyway, thank you, Michel
Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653924 is a reply to message #653923] Fri, 22 July 2016 02:47 Go to previous messageGo to next message
Michel Cadot
Messages: 68624
Registered: March 2007
Location: Nanterre, France, http://...
Senior Member
Account Moderator

So you see the link? I think this is your solution.

Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653925 is a reply to message #653924] Fri, 22 July 2016 02:57 Go to previous messageGo to next message
hui shen
Messages: 15
Registered: July 2016
Junior Member
Yes, I tried this; this solution works fine when using static SQL; but it seems do not work with dynamic SQL.
Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653938 is a reply to message #653925] Fri, 22 July 2016 09:49 Go to previous messageGo to next message
Michel Cadot
Messages: 68624
Registered: March 2007
Location: Nanterre, France, http://...
Senior Member
Account Moderator

Seems strange, there is no difference for Oracle id the statement that has been prepared is static or dynamic when you fetch.
Or, if you prefer, when you fetch, Oracle does not know if the statement was dynamic or static, it is not more than a cursor for it.

Test, with the same code, with a dynamic and a static statement and verify if there is any difference in the descriptor.

Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653986 is a reply to message #653938] Sun, 24 July 2016 20:59 Go to previous messageGo to next message
hui shen
Messages: 15
Registered: July 2016
Junior Member
Hi Michel, this is the usage different between a static and dynamic fetch
1. static
01 HOST-VAR-RECORD PIC X(80) VARYING. # declare the host variable

EXEC SQL DECLARE CURCOR_1 CURSOR ... END-EXEC. # SELECT CCC FROM TESTTAB
EXEC SQL OPEN CURCOR_1 END-EXEC.
EXEC SQL FETCH CURCOR_1 INTO :HOST-VAR-RECORD END-EXEC. # FETCH the cursor into host variable

Then
HOST-VAR-RECORD-LEN will have the real data length, i.e., 4
HOST-VAR-RECORD-ARR will have value "1234 ..."

2. dynamic fetch
01 SELDSC.
02 ...
02 ...

EXEC SQL FETCH CURCOR_1 USING DESCRIPTOR SELDSC END-EXEC. # Fetch the cursor, into SELDSC (that is defined by Oracle as standard structure for dynamic SQL communication).

Then I can retrieve column metadata information, and data value (appended with white spaces) from the SELDSC area; but there is no solution the get the real data length.
Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653987 is a reply to message #653986] Sun, 24 July 2016 23:35 Go to previous messageGo to next message
hui shen
Messages: 15
Registered: July 2016
Junior Member
In order to describe the problem, I'd like to post all my code
-bash-4.1$ cat -n DYNANSI.pco      
     1         IDENTIFICATION DIVISION.
     2         PROGRAM-ID.  DYNANSI.
     3         ENVIRONMENT DIVISION.
     4         DATA DIVISION.
     5         WORKING-STORAGE SECTION.
     6
     7             EXEC SQL BEGIN DECLARE SECTION END-EXEC.
     8         01 USERNAME PIC X(010).
     9         01 PASSWD PIC X(010).
    10         01 DBSTRING PIC X(020).
    11
    12         01 SDSC PIC X(6) VALUE "SELDSC".
    13         01 SELCNT PIC S9(9) COMP.
    14         01 SELNAME PIC X(80) VARYING.
    15         01 SELDATA PIC X(80).
    16         01 SELTYP PIC S9(4) COMP.
    17         01 SELPREC PIC S9(4) COMP.
    18         01 SELLEN PIC S9(4) COMP.
    19         01 SELRETLEN PIC S9(4) COMP.
    20         01 SELIND PIC S9(4) COMP.
    21         01 DYN-STATEMENT PIC X(80).
    22         01 SEL-INDEX PIC S9(4) COMP.
    23         01 ROW-INDEX PIC S9(4) COMP VALUE 0.
    24         01 VARCHAR2-TYP PIC S9(4) COMP VALUE 1.
    25         01 VAR-COUNT PIC 9(2).
    26         01 ROW-COUNT PIC 9(4).
    27         01 NO-MORE-DATA PIC X(1) VALUE "N".
    28         01 TMPLEN PIC S9(9) COMP.
    29         01 MAX-LENGTH PIC S9(9) COMP VALUE 80.
    30             EXEC SQL END DECLARE SECTION END-EXEC.
    31
    32             EXEC SQL INCLUDE SQLCA END-EXEC.
    33
    34         PROCEDURE DIVISION.
    35        * ALLOCATE THE BIND AND SELECT DESCRIPTORS.
    36             EXEC SQL WHENEVER SQLERROR GOTO SQL-ERROR END-EXEC.
    37             PERFORM LOGON.
    38             EXEC SQL ALLOCATE DESCRIPTOR :SDSC WITH MAX 20 END-EXEC.
    39
    40        * GET A SQL STATEMENT FROM THE OPERATOR.
    41             MOVE "SELECT C FROM TESTTAB" TO DYN-STATEMENT.
    42
    43        * PREPARE THE SQL STATEMENT AND DECLARE A CURSOR.
    44             EXEC SQL PREPARE S1 FROM :DYN-STATEMENT END-EXEC.
    45             EXEC SQL DECLARE C1 CURSOR FOR S1 END-EXEC.
    46
    47        * OPEN THE CURSOR AND DESCRIBE THE SELECT-LIST ITEMS.
    48         DESCRIBE-ITEMS.
    49             EXEC SQL OPEN C1 END-EXEC.
    50             EXEC SQL DESCRIBE OUTPUT S1 USING DESCRIPTOR :SDSC END-EXEC.
    51             EXEC SQL GET DESCRIPTOR :SDSC :SELCNT = COUNT END-EXEC.
    52             IF SELCNT < 0
    53               DISPLAY "TOO MANY SELECT-LIST ITEMS."
    54               GO TO END-SQL
    55             ELSE
    56               DISPLAY "NUMBER OF SELECT-LIST ITEMS: " WITH NO ADVANCING
    57               MOVE SELCNT TO VAR-COUNT
    58               DISPLAY VAR-COUNT
    59             END-IF.
    60
    61        * SET THE INPUT DESCRIPTOR
    62             IF SELCNT > 0
    63               PERFORM SET-SEL-DSC
    64                 VARYING SEL-INDEX FROM 1 BY 1
    65                 UNTIL SEL-INDEX > SELCNT
    66               DISPLAY " ".
    67     
    68        * FETCH EACH ROW AND PRINT EACH SELECT-LIST VALUE.
    69             IF SELCNT > 0
    70               PERFORM FETCH-ROWS UNTIL NO-MORE-DATA = "Y".
    71
    72             DISPLAY "NUMBER OF ROWS PROCESSED: " WITH NO ADVANCING.
    73             MOVE SQLERRD(3) TO ROW-COUNT.
    74             DISPLAY ROW-COUNT.
    75
    76        * CLEAN UP AND TERMINATE.
    77             EXEC SQL CLOSE C1 END-EXEC.
    78             EXEC SQL DEALLOCATE DESCRIPTOR :SDSC END-EXEC.
    79             DISPLAY " ".
    80             DISPLAY "HAVE A GOOD DAY!".
    81             DISPLAY " ".
    82             STOP RUN.
    83
    84        * DISPLAY ORACLE ERROR MESSAGE AND CODE.
    85         SQL-ERROR.
    86             DISPLAY " ".
    87             DISPLAY SQLERRMC.
    88         END-SQL.
    89             EXEC SQL WHENEVER SQLERROR CONTINUE END-EXEC.
    90             STOP RUN.
    91
    92         LOGON.
    93             MOVE "scott" TO USERNAME.
    94             MOVE "tiger" TO PASSWD.
    95             MOVE "orcl" TO DBSTRING.
    96             EXEC SQL
    97                CONNECT :USERNAME IDENTIFIED BY :PASSWD USING :DBSTRING
    98             END-EXEC.
    99             DISPLAY "SQLCODE: ", SQLCODE OF SQLCA.
   100             DISPLAY "CONNECTED TO DATABASE ", DBSTRING.
   101
   102        * SET A SELECT-LIST ELEMENT'S ATTRIBUTES
   103         SET-SEL-DSC.
   104             MOVE SPACES TO SELNAME-ARR.
   105             EXEC SQL GET DESCRIPTOR :SDSC VALUE :SEL-INDEX
   106               :SELNAME = NAME,
   107               :SELTYP  = TYPE,
   108               :SELPREC = PRECISION,
   109               :SELLEN  = LENGTH,
   110               :SELRETLEN  = RETURNED_LENGTH
   111             END-EXEC.
   112
   113             DISPLAY "COLUMN[", SEL-INDEX,
   114                     "]: SELNAME=[", SELNAME-ARR(1:SELNAME-LEN), "]",
   115                     ",SELTYP=",  SELTYP,
   116                     ",SELPREC=", SELPREC,
   117                     ",SELLEN=",  SELLEN,
   118                     ",SELRETLEN=",  SELRETLEN.
   119
   120        * FETCH A ROW AND PRINT THE SELECT-LIST VALUE.
   121         FETCH-ROWS.
   122             EXEC SQL FETCH C1 INTO DESCRIPTOR :SDSC END-EXEC.
   123             IF SQLCODE NOT = 0
   124               MOVE "Y" TO NO-MORE-DATA.
   125             IF SQLCODE = 0
   126               PERFORM PRINT-COLUMN-VALUES
   127                 VARYING SEL-INDEX FROM 1 BY 1
   128                 UNTIL SEL-INDEX > SELCNT.
   129
   130        * PRINT A SELECT-LIST VALUE.
   131         PRINT-COLUMN-VALUES.
   132             MOVE SPACES TO SELDATA.
   133             ADD 1 TO ROW-INDEX.
   134             EXEC SQL GET DESCRIPTOR :SDSC VALUE :SEL-INDEX
   135                  :SELDATA = DATA,
   136                  :SELIND = INDICATOR,
   137                  :SELLEN = LENGTH,
   138                  :SELRETLEN = RETURNED_LENGTH
   139             END-EXEC
   140             IF (SELIND = -1) MOVE "NULL" TO SELDATA.
   141             DISPLAY "ROW[" ROW-INDEX "]: ",
   142                     "LEN=",     SELLEN,
   143                     ",RETLEN=", SELRETLEN,
   144                     ",DATA=[",  SELDATA(1:SELLEN), "]".

And the compile and execution output:
procob include=../COPY iname=DYNANSI.pco release_cursor=no hold_cursor=no mode=ansi sqlcheck=syntax common_parser=yes lname=DYNANSI.lis oname=DYNANSI.cbl declare_section=no picx=charf db2_array=yes
cob -ug DYNANSI.cob -C "use(../../common/opt.dir)" -C "list(DYNANSI.lst)" -C XREF -C SETTINGS
Prepare input Oracle data
create table testtab(c varchar2(10));
insert into testtab values('111');
insert into testtab values(NULL);
insert into testtab values('4');
insert into testtab values('33');
Execution output:
$ rtsora DYNANSI.gnt
SQLCODE: +0000000000
CONNECTED TO DATABASE orcl                
NUMBER OF SELECT-LIST ITEMS: 01
COLUMN[+00001]: SELNAME=[C],SELTYP=+00012,SELPREC=+00000,SELLEN=+00004,SELRETLEN=+00000
 
ROW[+00001]: LEN=+00004,RETLEN=+00000,DATA=[111 ]
ROW[+00002]: LEN=+00004,RETLEN=+00000,DATA=[NULL]
ROW[+00003]: LEN=+00004,RETLEN=+00000,DATA=[4   ]
ROW[+00004]: LEN=+00004,RETLEN=+00000,DATA=[33  ]
NUMBER OF ROWS PROCESSED: 0004
 
HAVE A GOOD DAY!

We can find all information could be retrieved except the real data length (see output RETLEN field, that supposed to be get at source code line 138).
Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653989 is a reply to message #653987] Mon, 25 July 2016 00:42 Go to previous messageGo to next message
Michel Cadot
Messages: 68624
Registered: March 2007
Location: Nanterre, France, http://...
Senior Member
Account Moderator

Instead initializing the variable with spaces can't you fill it with a character that can't be in the data to see what is the returned value?
For instance, in your example, can you fill it with #?

Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653990 is a reply to message #653989] Mon, 25 July 2016 00:50 Go to previous messageGo to next message
hui shen
Messages: 15
Registered: July 2016
Junior Member
If i define buffer as PIC X(10), and initialize the buffer with string "1234567890" the result is:

- "111 567890" when column C value is "111", there is 1 white space after '1', and
- "4 567890" when column C value is "4", there is 3 white space after '4', and
- "33 567890" when column C value is "33", there is 2 white space after '3', and

That's to say, the white spaces are appended with max length of column definition length (i.e,. 4), the rest is untouched.

[Updated on: Mon, 25 July 2016 00:52]

Report message to a moderator

Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653991 is a reply to message #653990] Mon, 25 July 2016 01:03 Go to previous messageGo to next message
Michel Cadot
Messages: 68624
Registered: March 2007
Location: Nanterre, France, http://...
Senior Member
Account Moderator

So you have a workaround: you fill the buffer with characters that can't be in the data, before each fetch, then right trim them when you get these data.
I'm afraid I can't help you more than this, you can raise a SR on MOS if you want more explanation or another solution from it.

Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653992 is a reply to message #653991] Mon, 25 July 2016 01:08 Go to previous messageGo to next message
hui shen
Messages: 15
Registered: July 2016
Junior Member
Michel,

> So you have a workaround: you fill the buffer with characters that can't be in the data, before each fetch, then right trim them when you get these data.
This does not work with me; the key point is we cannot tell the difference whether a white space is part of the data content or is just appended by programming API.

> I'm afraid I can't help you more than this, you can raise a SR on MOS if you want more explanation or another solution from it.
I appreciate your help and comments very much, i will try.
Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653993 is a reply to message #653991] Mon, 25 July 2016 01:14 Go to previous messageGo to next message
Michel Cadot
Messages: 68624
Registered: March 2007
Location: Nanterre, France, http://...
Senior Member
Account Moderator
Maybe this is your solution: https://docs.oracle.com/cd/A57673_01/DOC/api/doc/PCO18/ch1.htm#toc017

Quote:
You can define a VARCHAR variable only in the Declare Section. Think of it as an extended COBOL datatype or predeclared group item. For example, the precompiler expands the VARCHAR declaration
         01  ENAME  PIC X(15) VARYING. 
into a group item with length and string fields, as follows:
         01  ENAME. 

             05  ENAME-LEN  PIC S9(4) COMP.

             05  ENAME-ARR  PIC X(15). 
The length field (suffixed with -LEN) holds the current length of the value stored in the string field (suffixed with -ARR). The maximum length in the VARCHAR host-variable declaration must be in the range of 1 to 65533 bytes.

Note: The keyword VARYING cannot be used when declaring multi-byte NLS character data.

The advantage of using VARCHAR variables is that you can explicitly set and reference the length field. With input host variables, Oracle reads the value of the length field and uses that many characters of the string field. With output host variables, Oracle sets the length value to the length of the character string stored in the string field.

Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653994 is a reply to message #653993] Mon, 25 July 2016 01:30 Go to previous messageGo to next message
hui shen
Messages: 15
Registered: July 2016
Junior Member
i think you have posted this like comment, and i have replied it; this is not a solution.
Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653996 is a reply to message #653994] Mon, 25 July 2016 02:16 Go to previous messageGo to next message
Michel Cadot
Messages: 68624
Registered: March 2007
Location: Nanterre, France, http://...
Senior Member
Account Moderator

Did you try?
Show me what happens when using this method with your example.
In your previous post you used SELDATA which is not VARYING and not SELNAME with its 2 fields.

Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653997 is a reply to message #653996] Mon, 25 July 2016 02:37 Go to previous messageGo to next message
hui shen
Messages: 15
Registered: July 2016
Junior Member
Hi Michel,
Could you look back to message #653986 ?
This solution is valid when handling static fetch SQL operation, but i am facing the problem with dynamic fetch SQL.
Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #653998 is a reply to message #653996] Mon, 25 July 2016 02:43 Go to previous messageGo to next message
hui shen
Messages: 15
Registered: July 2016
Junior Member
more,

with dynamic SQL, "ENAME" is regarded as a buffer space; it is not parsed a VARING buffer.

01 ENAME.
02 ENAME-LEN PIC S9(4) COMP.
02 ENAME-ARR PIC X(15).

procob/COBOL API treat ENAME as a while, so if column value is "123", then the first "12" will occupy the ENAME-LEN field, and '3' will occupy the ENAME-ARR(1) field.
Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #654000 is a reply to message #653998] Mon, 25 July 2016 03:43 Go to previous messageGo to next message
Michel Cadot
Messages: 68624
Registered: March 2007
Location: Nanterre, France, http://...
Senior Member
Account Moderator

Please open a SR to Oracle.

Also:
Quote:
> So you have a workaround: you fill the buffer with characters that can't be in the data, before each fetch, then right trim them when you get these data.
This does not work with me; the key point is we cannot tell the difference whether a white space is part of the data content or is just appended by programming API.

As I said, fill the buffer, before each fetch, with a character that can't be in your data, so does not choose a space.
In addition, use a buffer with length greater than the table column then you are sure that the last space is NOT part of your data. It is an easy workaround.

Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #654004 is a reply to message #654000] Mon, 25 July 2016 04:08 Go to previous messageGo to next message
hui shen
Messages: 15
Registered: July 2016
Junior Member
Quote:
As I said, fill the buffer, before each fetch, with a character that can't be in your data, so does not choose a space.
In addition, use a buffer with length greater than the table column then you are sure that the last space is NOT part of your data. It is an easy workaround.


This is not work also; let me explain to you.
1. define a buffer with PIC X(10)
2. support Oracle field is defined as VARCHAR(4)
3. support Oracle data value is "12"

step 1: initialize buffer with "AAAAAAAAAA" (10 times of "A")
move "AAAAAAAAAA" to DATA-BUFFER.

result: DATA-BUFFER="AAAAAAAAAA" (10 times of "A")
step 2:
FETCH DATA
result: DATA-BUFFER="12__AAAAAA"
the buffer with a '1', and a '2', and 2 white spaces, and 6 'A'.

step 3:
if database value is "12", "12_", "12__", they got the same result; i cannot tell the difference, right ?
Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #654008 is a reply to message #654004] Mon, 25 July 2016 04:46 Go to previous messageGo to next message
Michel Cadot
Messages: 68624
Registered: March 2007
Location: Nanterre, France, http://...
Senior Member
Account Moderator

What is your Oracle versions (database, client, Pro*Cobol)?

Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #654010 is a reply to message #654008] Mon, 25 July 2016 06:10 Go to previous messageGo to next message
hui shen
Messages: 15
Registered: July 2016
Junior Member
11.2.0.1.0

See Oracle client/server:
-bash-4.1$ sqlplus scott/tiger@orcl

SQL*Plus: Release 11.2.0.1.0 Production on Mon Jul 25 04:11:39 2016

Copyright (c) 1982, 2009, Oracle. All rights reserved.


Connected to:
Oracle Database 11g Enterprise Edition Release 11.2.0.1.0 - 64bit Production
With the Partitioning, OLAP, Data Mining and Real Application Testing options

See Oracle procob:
-bash-4.1$ procob

Pro*COBOL: Release 11.2.0.1.0 - Production on Mon Jul 25 04:12:38 2016

Copyright (c) 1982, 2009, Oracle and/or its affiliates. All rights reserved.

System default option values taken from: /home/oracle/app/product/11.2.0/db_1/precomp/admin/pcbcfg.cfg
Re: Pro*COBOL Dynamic SQL How to get data length of a VARCHAR2 column [message #654024 is a reply to message #654010] Mon, 25 July 2016 08:14 Go to previous message
Michel Cadot
Messages: 68624
Registered: March 2007
Location: Nanterre, France, http://...
Senior Member
Account Moderator

I think you have to open a SR to Oracle but (unless it is a known bug) the first thing they will tell you is to upgrade to the latest patchset: 11.2.0.4.

Previous Topic: Error in Pro*C file compile
Next Topic: ENV Vars for ProC on Linux
Goto Forum:
  


Current Time: Thu Mar 28 07:18:43 CDT 2024