Skip to main content

Hello,

I need to create safearray (to pass it into COM object outside Cobol), and each item in this safearray must be PIC N string.

I am using this code:

move VT-BSTR to w-vartype move 1 to w-dimension move xx-z to cElements of w-saBound(1) move 0 to llBound of w-saBound(1) invoke OLESafeArray "new" using by value w-vartype w-dimension by reference w-saBound(1) returning w-hostArray end-invoke perform varying w-Index from 0 by 1 until w-Index >= xx-z invoke w-hostArray "putString" using by reference w-Index by value 100 by reference w-item(w-Index 1) returning w-hresult end-invoke end-perform

Where w-item is PIC N(100). But it's not working, on the other side in C#, I receive in string variable complete gibberish. I think that "putString" accepts only PIC X.

So how to create safearray with Unicode strings?


#COBOL

Hello,

I need to create safearray (to pass it into COM object outside Cobol), and each item in this safearray must be PIC N string.

I am using this code:

move VT-BSTR to w-vartype move 1 to w-dimension move xx-z to cElements of w-saBound(1) move 0 to llBound of w-saBound(1) invoke OLESafeArray "new" using by value w-vartype w-dimension by reference w-saBound(1) returning w-hostArray end-invoke perform varying w-Index from 0 by 1 until w-Index >= xx-z invoke w-hostArray "putString" using by reference w-Index by value 100 by reference w-item(w-Index 1) returning w-hresult end-invoke end-perform

Where w-item is PIC N(100). But it's not working, on the other side in C#, I receive in string variable complete gibberish. I think that "putString" accepts only PIC X.

So how to create safearray with Unicode strings?


#COBOL

BSTR stores Unicode data by default so they should be able to pass PIC N data items directly.

Are you setting the NSYMBOL"NATIONAL" directive in your NX program so that PIC N is stored as Unicode instead of DBCS?

Can you show me what your C# interface code looks like that is accepting the SafeArray?

You might try storing the PIC N data as a variant using the method setString and then store the variants in the Safearray instead of the BSTR. The docs state that the string will be stored as Unicode.

OLEVariant Method setString

Store a string of length theStringLength in this instance. Pass theStringLength BY VALUE and theString BY REFERENCE. The current contents of this variant are freed. The string is stored as a Unicode BSTR in the variant.


BSTR stores Unicode data by default so they should be able to pass PIC N data items directly.

Are you setting the NSYMBOL"NATIONAL" directive in your NX program so that PIC N is stored as Unicode instead of DBCS?

Can you show me what your C# interface code looks like that is accepting the SafeArray?

You might try storing the PIC N data as a variant using the method setString and then store the variants in the Safearray instead of the BSTR. The docs state that the string will be stored as Unicode.

OLEVariant Method setString

Store a string of length theStringLength in this instance. Pass theStringLength BY VALUE and theString BY REFERENCE. The current contents of this variant are freed. The string is stored as a Unicode BSTR in the variant.

I put together a real simple example that demonstrates invoking a C# COM Server and passing in both a SafeArray storing PIC X data items as strings and a SafeArray storing PIC N data items as strings. The C# COM Server will display all the items passed in for each one.

 

$set ooctrl( p) $set nsymbol"NATIONAL" identification division. program-id. COBOLClient. environment division. configuration section. class-control. csCOMClass is class "$OLE$csCOMClass2.csCOMClass2" OleSafeArray is class "olesafea". working-storage section. copy "MFOLE.cpy". copy "olesafea.cpy". 01 w-saBound SAFEARRAYBOUND occurs 1. 01 w-hostArray object reference. 01 w-varType pic 9(4) comp-5. 01 w-dimension pic x(4) comp-5. 01 w-hresult pic x(4) comp-5. 01 anInstance object reference. 01 picxarray. 05 aString pic x(25) occurs 3 times values "This is from COBOL #1" "This is from COBOL #2" "This is from COBOL #3". 01 picnarray. 05 aNString pic N(30) occurs 3 times values N"This is Unicode from COBOL #1" N"This is Unicode from COBOL #2" N"This is Unicode from COBOL #3". 01 w-index pic x(4) comp-5 occurs 1 times value zeroes. 01 strLength pic x(4) comp-5 value zeroes. 01 any-key pic x. procedure division. *> Create an instance of the C# COM Server invoke csCOMClass "new" returning anInstance perform 100-create-safearray perform 105-invoke-method-with-picx perform 110-invoke-method-with-picn display "Press enter to quit" accept any-key stop run. 100-create-safearray. move VT-BSTR to w-vartype move 1 to w-dimension move 3 to cElements of w-saBound(1) move 0 to llBound of w-saBound(1) invoke OLESafeArray "new" using by value w-vartype w-dimension by reference w-saBound(1) returning w-hostArray end-invoke. 105-invoke-method-with-picx. move length of aString to strLength perform varying w-Index(1) from 0 by 1 until w-index(1) = 3 invoke w-hostArray "putString" using by reference w-Index(1) by value strLength by reference aString(w-Index(1) 1) returning w-hresult end-invoke end-perform invoke anInstance "csCOMMethod" using by value w-hostarray returning w-hresult end-invoke. 110-invoke-method-with-picn. move length of aNString to strLength perform varying w-Index(1) from 0 by 1 until w-index(1) = 3 invoke w-hostArray "putString" using by reference w-Index(1) by value strLength by reference aNString(w-Index(1) 1) returning w-hresult end-invoke end-perform invoke anInstance "csCOMMethod" using by value w-hostarray returning w-hresult end-invoke.

 

using System; using System.Collections.Generic; using System.Linq; using System.Text; using System.Threading.Tasks; using System.Runtime.InteropServices; namespace csCOMClass2 { [ComVisible(true)] [InterfaceType(ComInterfaceType.InterfaceIsDual)] public interface IcsCOMClass2 { int csCOMMethod( [In, MarshalAs(UnmanagedType.SafeArray, SafeArraySubType = VarEnum.VT_BSTR)] string[] s); } [ComVisible(true)] [ClassInterface(ClassInterfaceType.None)] [ProgId("csCOMClass2.csCOMClass2")] public class csCOMClass2 : IcsCOMClass2 { public csCOMClass2() { } ~csCOMClass2() { } public int csCOMMethod( [In, MarshalAs(UnmanagedType.SafeArray, SafeArraySubType = VarEnum.VT_BSTR)] string[] s) { foreach (string passedstring in s) { Console.WriteLine("This is string " passedstring); } return 0; } } }

I put together a real simple example that demonstrates invoking a C# COM Server and passing in both a SafeArray storing PIC X data items as strings and a SafeArray storing PIC N data items as strings. The C# COM Server will display all the items passed in for each one.

 

$set ooctrl( p) $set nsymbol"NATIONAL" identification division. program-id. COBOLClient. environment division. configuration section. class-control. csCOMClass is class "$OLE$csCOMClass2.csCOMClass2" OleSafeArray is class "olesafea". working-storage section. copy "MFOLE.cpy". copy "olesafea.cpy". 01 w-saBound SAFEARRAYBOUND occurs 1. 01 w-hostArray object reference. 01 w-varType pic 9(4) comp-5. 01 w-dimension pic x(4) comp-5. 01 w-hresult pic x(4) comp-5. 01 anInstance object reference. 01 picxarray. 05 aString pic x(25) occurs 3 times values "This is from COBOL #1" "This is from COBOL #2" "This is from COBOL #3". 01 picnarray. 05 aNString pic N(30) occurs 3 times values N"This is Unicode from COBOL #1" N"This is Unicode from COBOL #2" N"This is Unicode from COBOL #3". 01 w-index pic x(4) comp-5 occurs 1 times value zeroes. 01 strLength pic x(4) comp-5 value zeroes. 01 any-key pic x. procedure division. *> Create an instance of the C# COM Server invoke csCOMClass "new" returning anInstance perform 100-create-safearray perform 105-invoke-method-with-picx perform 110-invoke-method-with-picn display "Press enter to quit" accept any-key stop run. 100-create-safearray. move VT-BSTR to w-vartype move 1 to w-dimension move 3 to cElements of w-saBound(1) move 0 to llBound of w-saBound(1) invoke OLESafeArray "new" using by value w-vartype w-dimension by reference w-saBound(1) returning w-hostArray end-invoke. 105-invoke-method-with-picx. move length of aString to strLength perform varying w-Index(1) from 0 by 1 until w-index(1) = 3 invoke w-hostArray "putString" using by reference w-Index(1) by value strLength by reference aString(w-Index(1) 1) returning w-hresult end-invoke end-perform invoke anInstance "csCOMMethod" using by value w-hostarray returning w-hresult end-invoke. 110-invoke-method-with-picn. move length of aNString to strLength perform varying w-Index(1) from 0 by 1 until w-index(1) = 3 invoke w-hostArray "putString" using by reference w-Index(1) by value strLength by reference aNString(w-Index(1) 1) returning w-hresult end-invoke end-perform invoke anInstance "csCOMMethod" using by value w-hostarray returning w-hresult end-invoke.

 

using System; using System.Collections.Generic; using System.Linq; using System.Text; using System.Threading.Tasks; using System.Runtime.InteropServices; namespace csCOMClass2 { [ComVisible(true)] [InterfaceType(ComInterfaceType.InterfaceIsDual)] public interface IcsCOMClass2 { int csCOMMethod( [In, MarshalAs(UnmanagedType.SafeArray, SafeArraySubType = VarEnum.VT_BSTR)] string[] s); } [ComVisible(true)] [ClassInterface(ClassInterfaceType.None)] [ProgId("csCOMClass2.csCOMClass2")] public class csCOMClass2 : IcsCOMClass2 { public csCOMClass2() { } ~csCOMClass2() { } public int csCOMMethod( [In, MarshalAs(UnmanagedType.SafeArray, SafeArraySubType = VarEnum.VT_BSTR)] string[] s) { foreach (string passedstring in s) { Console.WriteLine("This is string " passedstring); } return 0; } } }

Hello Chris,

thanks for your sample code. I try it, but result is still not working correctly for me. A just slightly modified it in this way:

First item of PIC N array, I replace with value readed from DB, it's text in cyrillic: ЁЖЗИЙ 

In below is my COBOL and C# code, and results which I receive. Please what I am doing wrong?

C $SET DIRECTIVES (SBODBC.DIR) NSYMBOL"NATIONAL" $set ooctrl( p) identification division. program-id. COBOLClient. environment division. configuration section. class-control. csCOMClass is class "$OLE$csCOMClass2.csCOMClass2" OleSafeArray is class "olesafea". working-storage section. copy "MFOLE.cpy". copy "olesafea.cpy". 01 w-saBound SAFEARRAYBOUND occurs 1. 01 w-hostArray object reference. 01 w-varType pic 9(4) comp-5. 01 w-dimension pic x(4) comp-5. 01 w-hresult pic x(4) comp-5. 01 anInstance object reference. 01 picxarray. 05 aString pic x(25) occurs 3 times values "This is from COBOL #1" "This is from COBOL #2" "This is from COBOL #3". 01 picnarray. 05 aNString pic N(30) occurs 3 times values N"This is Unicode from COBOL #1" N"This is Unicode from COBOL #2" N"This is Unicode from COBOL #3". 01 w-index pic x(4) comp-5 occurs 1 times value zeroes. 01 strLength pic x(4) comp-5 value zeroes. 01 any-key pic x. 01 w1 pic n(100). 01 w-sql pic x(100). EXEC SQL BEGIN DECLARE SECTION END-EXEC. * 01 MFSQLMESSAGETEXT PIC X(600). 01 WS-CONNECTSTRING PIC X(150). 01 WS-DATABASE PIC X(32). 01 WS-SERVER PIC X(80). 01 WS-HOSTVAR PIC X(250). 01 H-SQL-STATEMENT PIC X(700). 01 H-DESC PIC N(4). EXEC SQL END DECLARE SECTION END-EXEC. EXEC SQL INCLUDE SQLCA END-EXEC. procedure division. EXEC SQL DECLARE CUR_READ CURSOR FOR STMT_READ END-EXEC. MOVE "CZDMV023" TO WS-SERVER MOVE "SunSystemsData" TO WS-DATABASE PERFORM SZ1000-CONNECT-TO-DB initialize w-sql w1 string "SELECT ACCOUNT" " FROM LLPSY_PK1_LLP_BMP" delimited by size into w-sql EXEC SQL PREPARE STMT_READ FROM :w-sql END-EXEC EXEC SQL OPEN CUR_READ END-EXEC. EXEC SQL FETCH CUR_READ INTO :w1 END-EXEC EXEC SQL CLOSE CUR_READ END-EXEC. exec sql commit end-exec move w1 to aNString(1) *> Create an instance of the C# COM Server invoke csCOMClass "new" returning anInstance perform 100-create-safearray perform 105-invoke-method-with-picx perform 110-invoke-method-with-picn display "Press enter to quit" accept any-key stop run. 100-create-safearray. move VT-BSTR to w-vartype move 1 to w-dimension move 3 to cElements of w-saBound(1) move 0 to llBound of w-saBound(1) invoke OLESafeArray "new" using by value w-vartype w-dimension by reference w-saBound(1) returning w-hostArray end-invoke. 105-invoke-method-with-picx. move length of aString to strLength perform varying w-Index(1) from 0 by 1 until w-index(1) = 3 invoke w-hostArray "putString" using by reference w-Index(1) by value strLength by reference aString(w-Index(1) 1) returning w-hresult end-invoke end-perform invoke anInstance "csCOMMethod" using by value w-hostarray returning w-hresult end-invoke. 110-invoke-method-with-picn. move length of aNString to strLength perform varying w-Index(1) from 0 by 1 until w-index(1) = 3 invoke w-hostArray "putString" using by reference w-Index(1) by value strLength by reference aNString(w-Index(1) 1) returning w-hresult end-invoke end-perform invoke anInstance "csCOMMethod" using by value w-hostarray returning w-hresult end-invoke. SZ1000-CONNECT-TO-DB SECTION. ******************************************************************* * Connect to database * ******************************************************************* Z1000-START. MOVE SPACES TO WS-CONNECTSTRING. STRING "DRIVER={SQL Server};" DELIMITED BY SIZE ";DATABASE=" WS-DATABASE DELIMITED BY "|" ";SERVER=" WS-SERVER DELIMITED BY "|" ";AutoTranslate=no" DELIMITED BY SPACE ";Trusted_Connection=yes" DELIMITED BY SIZE INTO WS-CONNECTSTRING END-STRING EXEC SQL CONNECT USING :WS-CONNECTSTRING RETURNING :WS-HOSTVAR END-EXEC. * Z1000-EXIT. EXIT.

 

using System; using System.Collections.Generic; using System.Linq; using System.Text; using System.Threading.Tasks; using System.Runtime.InteropServices; namespace csCOMClass2 { [Guid("832A808B-D02D-493A-BF04-1841D9E2361B")] [InterfaceType(ComInterfaceType.InterfaceIsDual)] public interface IcsCOMClass2 { int csCOMMethod( [In, MarshalAs(UnmanagedType.SafeArray, SafeArraySubType = VarEnum.VT_BSTR)] string[] s); } [Guid("EBE74093-0417-4506-8BDD-C9CF9239B2AB")] [ClassInterface(ClassInterfaceType.None)] [ProgId("csCOMClass2.csCOMClass2")] public class csCOMClass2 : IcsCOMClass2 { public csCOMClass2() { } ~csCOMClass2() { } public int csCOMMethod( [In, MarshalAs(UnmanagedType.SafeArray, SafeArraySubType = VarEnum.VT_BSTR)] string[] s) { Console.ReadKey(); foreach (string passedstring in s) { Console.WriteLine("This is string " passedstring); } return 0; } } }

I put together a real simple example that demonstrates invoking a C# COM Server and passing in both a SafeArray storing PIC X data items as strings and a SafeArray storing PIC N data items as strings. The C# COM Server will display all the items passed in for each one.

 

$set ooctrl( p) $set nsymbol"NATIONAL" identification division. program-id. COBOLClient. environment division. configuration section. class-control. csCOMClass is class "$OLE$csCOMClass2.csCOMClass2" OleSafeArray is class "olesafea". working-storage section. copy "MFOLE.cpy". copy "olesafea.cpy". 01 w-saBound SAFEARRAYBOUND occurs 1. 01 w-hostArray object reference. 01 w-varType pic 9(4) comp-5. 01 w-dimension pic x(4) comp-5. 01 w-hresult pic x(4) comp-5. 01 anInstance object reference. 01 picxarray. 05 aString pic x(25) occurs 3 times values "This is from COBOL #1" "This is from COBOL #2" "This is from COBOL #3". 01 picnarray. 05 aNString pic N(30) occurs 3 times values N"This is Unicode from COBOL #1" N"This is Unicode from COBOL #2" N"This is Unicode from COBOL #3". 01 w-index pic x(4) comp-5 occurs 1 times value zeroes. 01 strLength pic x(4) comp-5 value zeroes. 01 any-key pic x. procedure division. *> Create an instance of the C# COM Server invoke csCOMClass "new" returning anInstance perform 100-create-safearray perform 105-invoke-method-with-picx perform 110-invoke-method-with-picn display "Press enter to quit" accept any-key stop run. 100-create-safearray. move VT-BSTR to w-vartype move 1 to w-dimension move 3 to cElements of w-saBound(1) move 0 to llBound of w-saBound(1) invoke OLESafeArray "new" using by value w-vartype w-dimension by reference w-saBound(1) returning w-hostArray end-invoke. 105-invoke-method-with-picx. move length of aString to strLength perform varying w-Index(1) from 0 by 1 until w-index(1) = 3 invoke w-hostArray "putString" using by reference w-Index(1) by value strLength by reference aString(w-Index(1) 1) returning w-hresult end-invoke end-perform invoke anInstance "csCOMMethod" using by value w-hostarray returning w-hresult end-invoke. 110-invoke-method-with-picn. move length of aNString to strLength perform varying w-Index(1) from 0 by 1 until w-index(1) = 3 invoke w-hostArray "putString" using by reference w-Index(1) by value strLength by reference aNString(w-Index(1) 1) returning w-hresult end-invoke end-perform invoke anInstance "csCOMMethod" using by value w-hostarray returning w-hresult end-invoke.

 

using System; using System.Collections.Generic; using System.Linq; using System.Text; using System.Threading.Tasks; using System.Runtime.InteropServices; namespace csCOMClass2 { [ComVisible(true)] [InterfaceType(ComInterfaceType.InterfaceIsDual)] public interface IcsCOMClass2 { int csCOMMethod( [In, MarshalAs(UnmanagedType.SafeArray, SafeArraySubType = VarEnum.VT_BSTR)] string[] s); } [ComVisible(true)] [ClassInterface(ClassInterfaceType.None)] [ProgId("csCOMClass2.csCOMClass2")] public class csCOMClass2 : IcsCOMClass2 { public csCOMClass2() { } ~csCOMClass2() { } public int csCOMMethod( [In, MarshalAs(UnmanagedType.SafeArray, SafeArraySubType = VarEnum.VT_BSTR)] string[] s) { foreach (string passedstring in s) { Console.WriteLine("This is string " passedstring); } return 0; } } }

And here are my results:

what I see in cmd when I am running program:

And what I see in Visual Studio in debug:


And here are my results:

what I see in cmd when I am running program:

And what I see in Visual Studio in debug:

Please is there any chance how to solve this problem described in previous posts?

Please is there any chance how to solve this problem described in previous posts?

The passing of Unicode data directly as a BSTR in a SafeArray does not appear to be supported. PIC N is not one of the data types that is documented.

I got this to work by redefining the PIC N fields as PIC X with double the length and then passing these as an array of unsigned character types (Byte in C#).
This then gets converted back to a Unicode String in C#.

Here is a very simple example:

$set ooctrl( p) $set nsymbol"NATIONAL" identification division. program-id. COBOLClient. environment division. configuration section. class-control. csCOMClass is class "$OLE$csCOMClass2.csCOMClass2" OleSafeArray is class "olesafea". working-storage section. copy "MFOLE.cpy". copy "olesafea.cpy". 01 w-saBound SAFEARRAYBOUND occurs 1. 01 w-hostArray object reference. 01 w-varType pic 9(4) comp-5. 01 w-dimension pic x(4) comp-5. 01 w-hresult pic x(4) comp-5. 01 anInstance object reference. 01 my-unicode pic n(30) value N"This is Cyrilac ЀЂЃ". 01 my-picx pic X comp-5 occurs 60 times redefines my-unicode. 01 w-index pic x(4) comp-5 occurs 1 times value zeroes. 01 any-key pic x. 01 my-pointer pointer. procedure division. *> Create an instance of the C# COM Server invoke csCOMClass "new" returning anInstance perform 100-create-safearray perform 105-invoke-method-with-picx display "Press enter to quit" accept any-key stop run. 100-create-safearray. *> array is defined as unsigned 1 byte char move VT-UI1 to w-vartype move 1 to w-dimension move 60 to cElements of w-saBound(1) move 0 to llBound of w-saBound(1) invoke OLESafeArray "new" using by value w-vartype w-dimension by reference w-saBound(1) returning w-hostArray end-invoke. 105-invoke-method-with-picx. perform varying w-index(1) from 0 by 1 until w-index(1) = 60 set my-pointer to address of my-picx(w-index(1) 1) invoke w-hostArray "putElement" using by reference w-index(1) by value my-pointer returning w-hresult end-invoke end-perform invoke anInstance "csCOMMethod" using by value w-hostarray returning w-hresult end-invoke.

and the C# code:

using System; using System.Text; using System.Runtime.InteropServices; namespace csCOMClass2 { [ComVisible(true)] [InterfaceType(ComInterfaceType.InterfaceIsDual)] public interface IcsCOMClass2 { int csCOMMethod( [In, MarshalAs(UnmanagedType.SafeArray, SafeArraySubType = VarEnum.VT_UI1)] Byte[] s); } [ComVisible(true)] [ClassInterface(ClassInterfaceType.None)] [ProgId("csCOMClass2.csCOMClass2")] public class csCOMClass2 : IcsCOMClass2 { public csCOMClass2() { } ~csCOMClass2() { } public int csCOMMethod( [In, MarshalAs(UnmanagedType.SafeArray, SafeArraySubType = VarEnum.VT_UI1)] Byte[] s) { string utfString = Encoding.Unicode.GetString(s, 0, s.Length); Console.OutputEncoding = System.Text.Encoding.Unicode; Console.WriteLine(utfString); return 0; } } }