From: Pete Dashwood on
Pete Dashwood wrote:
>
> If I get a chance I'll try and duplicate your problem.
>
> Pete.
I was doing some other Excel related stuff today so I took some time out to
look at your problem.

I was able to get the same result you did, so I decided to solve it :-)

The error message you got was telling you the Method did not exist, and it
doesn't.

I mentioned earlier that the object model shows the method as simply
"PrintArea" NOT "setPrintArea".

So I did some experiments...

Here's the code (in Fujitsu NetCOBOL which is NOT .NET code and does NOT
generate CLR. This is standard unmanaged code).

PROGRAM-ID. XLTEST.
* written by Pete Dashwood, PRIMA Computing, (NZ) Ltd. January 2010.
* (some parts loosely based on Fujitsu sample code)
ENVIRONMENT DIVISION.
CONFIGURATION SECTION.
REPOSITORY.
Class COM AS "*COM".
DATA DIVISION.
WORKING-STORAGE SECTION.
01 ExcelProgID pic x(20) value "Excel.Application.12".

01 objExcel OBJECT REFERENCE COM.
01 objWorkbooks OBJECT REFERENCE COM.
01 objWkBk OBJECT REFERENCE COM.
01 objWorksheets OBJECT REFERENCE COM.
01 objCurrSheet OBJECT REFERENCE COM.
01 objSelectCell OBJECT REFERENCE COM.
01 objRangeBegin OBJECT REFERENCE COM.
01 objRangeEnd OBJECT REFERENCE COM.
01 objRange OBJECT REFERENCE COM.
01 objCell OBJECT REFERENCE COM.
01 objPageSetUp OBJECT REFERENCE COM.

01 CellLine PIC S9(9) COMP-5.
01 CellCol PIC S9(9) COMP-5.
01 COMTrue PIC 1(1) BIT VALUE B"1". *> Ugh!!!
01 Print-Range-String PIC X(20).
01 numDisplay PIC 999.

01 Test-Value pic x(35) value "Print".
PROCEDURE DIVISION.
Main section.
000.
*======================================================================
* Activate Excel.
*======================================================================

invoke COM "CREATE-OBJECT"
USING ExcelProgID
RETURNING objExcel
end-invoke
invoke objExcel "SET-VISIBLE"
USING COMTrue
end-invoke
*======================================================================
* Create a new Workbook
*======================================================================
*
invoke objExcel "GET-WORKBOOKS" *> Get the Workbook object.
RETURNING objWorkbooks
end-invoke
invoke objWorkbooks "Add"
RETURNING objWkbk
end-invoke
invoke objWkBk "Activate" end-invoke
*======================================================================
* Create a new sheet in the new workbook and get a reference to it
*======================================================================
invoke objWkBk "GET-WORKSHEETS"
RETURNING objWorksheets
end-invoke
invoke objWorksheets "Add" *> makes the new sheet active also...
end-invoke
*> get a reference to the current sheet in the new workbook
invoke objWkBk "GET-ACTIVESHEET"
RETURNING objCurrSheet
end-invoke
*======================================================================
* Set the value for 1st - 10th Cell (A1 to J1) in the new sheet
* We will print cells 1 - 7 but not the rest...
*======================================================================
move 1 to CellLine.
perform
varying CellCol
from 1
by 1
until CellCol > 10
invoke objCurrSheet "GET-CELLS"
USING CellLine CellCol
RETURNING objCell
end-invoke
move spaces to test-value
if CellCol > 7
move "Don't print" to test-value
move CellCol to numDisplay
move numDisplay to test-value (13:3)
else
move "Print" to test-value
move CellCol to numDisplay
move numDisplay to test-value (7:3)
end-if

invoke objCell "SET-VALUE"
USING test-value
end-invoke
end-perform
*======================================================================
* Select the 1st - 7th Cell in the 1st line (from A1 to J1).
*======================================================================
move 1 to CellLine
move 1 to CellCol *> Get the beginning position of
invoke objCurrSheet "GET-CELLS" *> the Cell object.
USING CellLine CellCol
RETURNING objRangeBegin
end-invoke
MOVE 1 TO CellLine
MOVE 7 TO CellCol *> Get the ending position of the
invoke objCurrSheet "GET-CELLS" *> Cell object.
USING CellLine CellCol
RETURNING objRangeEnd
end-invoke
invoke objCurrSheet "GET-RANGE"
USING objRangeBegin objRangeEnd
RETURNING objRange
end-invoke
*======================================================================
* Set the visible print area
*
* This has to be in A1 style address format. Use the "Address"
* property of the range to get this.
*======================================================================
invoke objRange "GET-Address"
returning Print-Range-String
end-invoke
*> Get a reference to the sheet's PageSetup
invoke objCurrSheet "GET-PageSetUp"
returning objPageSetUp
end-invoke
*> Add the visible print area to the sheet's PageSetup
invoke objPageSetUp "SET-PrintArea"
using Print-Range-String
end-invoke
*> At this point cells 1 - 7 appear on the spread sheet
*> with a dotted frame around them
*======================================================================
* Print the Cells...
* uses the default printer.
*======================================================================
invoke objCurrSheet "PrintOut"
end-invoke
*> ONLY the specified range is printed...

.
999.
exit program
.
END PROGRAM XLTEST.


This gives the expected result. However, if I change the line that sets up
the print area to be:

*> Add the visible print area to the sheet's PageSetup
invoke objPageSetUp "SET-setPrintArea"
using Print-Range-String
end-invoke

....it fails with exactly the equivalent error code you received... (There is
no such object as "setPrintArea")

Here's the code you posted, annotated as to why it's wrong, and corrected.

>
>> Move z"1:267" TO X-00-TEXT => NO! it must be in A1 format... use
>> "$A$1:$EA$267"

>
>> INVOKE WorkBook "getActiveSheet" RETURNING ActiveSheet.
>
>> INVOKE ActiveSheet "getPageSetup" Returning PageSetup.
>
>> INVOKE PageSetup "setPrintArea" using X-00-TEXT => INVOKE PageSetup
>> "PrintArea" using X-00-TEXT

(You might need to check whether Micro Focus have SET methods for Automation
servers as part of their interface to COM. It is possible that the USING
tells the server to SET the value and returning tells it to GET the value. I
haven't used COM with MicroFocus and I have requested people who ARE using
it, to let us have the code for the http://primacomputing.co.nz/cobol21
site. So far no-one has responded... perhaps you might be first? :-))

That should fix it.

So, I lose my bet that the problem is with X-00-TEXT... :-) The problem is
with the name of the attribute.

I suspect that sample code you looked at may have been using a set method
for the particular platform to set it. The Fujitsu COM interface
automatically builds GET and SET methods for PROPERTIES of COM objects and
you can see them being referenced in the program above.

The only definitive way to remove doubt when it comes to Object Oriented
Automation, is to consult the Object Model or an Object Browser.


Pete.
--
"I used to write COBOL...now I can do anything."