From: Pete Dashwood on
john(a)wexfordpress.com wrote:
> On Jan 18, 6:50 am, Alistair <alist...(a)ld50macca.demon.co.uk> wrote:
>> On Jan 16, 10:14 am, "Pete Dashwood"
>>
>>
>>
>> <dashw...(a)removethis.enternet.co.nz> wrote:
>>> Does anybody use Micro Focus COBOL (any version, procedural or OO)
>>> to access COM or Automation server code, or even to write a COM
>>> compliant server module? If you do, there is a COBOL sample program
>>> below, written in Fujitsu OO NetCOBOL that I would be very
>>> interested to see "translated" to Micro Focus. It is a very small
>>> program and shouldn't take anyone too long.
>>
>>> The Component Object Model provides an ideal platform for
>>> encapsulating functionality and making it available to other
>>> languages and platforms. As most of Microsoft Office is written as
>>> Automation servers, compliant with COM, it is also a very useful
>>> way to handle ACCESS, EXCEL, WORD and POWER POINT from within your
>>> own programs. Everything you can do manually with these packages
>>> can be done under program control, even from COBOL, via the COM
>>> interface. For example, the sample below is manipulating EXCEL, but
>>> it could equally well be ANY of the MS Office suite, as well as
>>> thousands of other COM compliant components.
>>
>>> If you accept this request, and have no objection, I'll place both
>>> sets of code on the cobol21 web site with suitable background and
>>> acknowledgement of source. I'll also wrap your code so it can be
>>> used with .NET if it isn't already a .NET Assembly.
>>
>>> Any takers?
>>
>>> 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.
>>
>>> Pete
>>
>>> --
>>> "I used to write COBOL...now I can do anything."
>>
>> I tried compiling this. Had to change all of the comments (MF uses *>
>> for comments) then ran in to the definition of ComTrue as a problem.
>> MF doesn't recognise the PIC and I could not find anything to match
>> the Fujitsu definition.
>
> I don't recognize this program as being standard COBOL.

Well posting it here does reformat it a bit. It looks better in a COBOL
IDE... :-)


>If you want to
> deal
> with such esoterica as COM I would use the language that others use to
> deal with
> such matters.

Esoterica? COM? :It is one of the single most used features of the
Microsoft environment and there's certianly nothing esoteric about. it. The
Component Object Model (COM) evolved from Online Linking and Embedding
which, in turn, was based on Dynamic Data Exchange (DDE). These things have
been with us for a couple of decades and, as a developer targeting mainly
Microsoft platforms, I have used all of these models from COBOL.

I don't know about "others" but I've been dealing with COM objects in COBOL
for at least 12 years now.

> Specifically I don't find these constructs in any COBOL
> document I have.

Try the documents that AREN'T illuminated on sheepskin... :-)

> In general the recent attempts to make COBOL into some kind of object-
> oriented language
> lead us down the wrong path.

Ah, departure from the One True Faith... I understand.


> I have been programming in COBOL for 42 years
43 for me.

> and I don't
> recognize half the statements in the above code.

Ok, shall I just throw the code away then? :-)

I have been programming in COBOL longer than you have (not that it matters,
but it apparently does to you) and I do recognize all of the statements...
plus a lot more I didn't use...and even more in at least 5 other programming
languages, plus 7 dialects of COBOL :-) But I don't generally refer to
myself as a programmer; there are REAL programmers in this forum.


>
> That defeats one of the purposes of any High Level Language:
> to be a language where programmer x can read, understand and modify a
> program written by
> programmer y.

Oh Dear. And here's me thnking all these years that High Level languages
were invented so code could be ported. (In low level languages it has to be
emulated)

But just because there exists some x that cannot "read, understand and
modify a program written by programmer y" does that mean all x cannot?

Does it mean y's program is useless?

Does it mean that y is "too clever by half"? Or isn't it possible that
there could be some x who CALL themselves "programmers" but really are only
programmers in the very most limited sense of the word?

Are you suggesting that programming should be pitched to the lowest common
denominator of skills?

Doing that leads to shops which ban use of PERFORM... VARYING, say all IF
statements must test TRUE, Reference Modification must not be used (because
some people have trouble with numbers), and all the other stupid and
restrictive standards that COBOL shops implement so that no-one has to think
or learn their craft.

John, I don't want you to take this personally, it isn't meant to wound, but
why would you post to a thread where I'm trying to get some serious support
so that something can be learned, just so you can Harrumph and tell us it
ISN'T COBOL, when it blatantly IS?

It just may not be COBOL as YOU know it.

That doesn't make it worthless.

Pete.

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


From: Pete Dashwood on
Alistair wrote:
> On Feb 3, 2:25 pm, "j...(a)wexfordpress.com" <j...(a)wexfordpress.com>
> wrote:
>> On Jan 18, 6:50 am, Alistair <alist...(a)ld50macca.demon.co.uk> wrote:
>>
>>
>>
>>
>>
>>> On Jan 16, 10:14 am, "Pete Dashwood"
>>
>>> <dashw...(a)removethis.enternet.co.nz> wrote:
>>>> Does anybody use Micro Focus COBOL (any version, procedural or OO)
>>>> to access COM or Automation server code, or even to write a COM
>>>> compliant server module? If you do, there is a COBOL sample
>>>> program below, written in Fujitsu OO NetCOBOL that I would be very
>>>> interested to see "translated" to Micro Focus. It is a very small
>>>> program and shouldn't take anyone too long.
>>
>>>> The Component Object Model provides an ideal platform for
>>>> encapsulating functionality and making it available to other
>>>> languages and platforms. As most of Microsoft Office is written as
>>>> Automation servers, compliant with COM, it is also a very useful
>>>> way to handle ACCESS, EXCEL, WORD and POWER POINT from within your
>>>> own programs. Everything you can do manually with these packages
>>>> can be done under program control, even from COBOL, via the COM
>>>> interface. For example, the sample below is manipulating EXCEL,
>>>> but it could equally well be ANY of the MS Office suite, as well
>>>> as thousands of other COM compliant components.
>>
>>>> If you accept this request, and have no objection, I'll place both
>>>> sets of code on the cobol21 web site with suitable background and
>>>> acknowledgement of source. I'll also wrap your code so it can be
>>>> used with .NET if it isn't already a .NET Assembly.
>>
>>>> Any takers?
>>
>>>> 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.
>>
>>>> Pete
>>
>>>> --
>>>> "I used to write COBOL...now I can do anything."
>>
>>> I tried compiling this. Had to change all of the comments (MF uses
>>> *> for comments) then ran in to the definition of ComTrue as a
>>> problem. MF doesn't recognise the PIC and I could not find anything
>>> to match the Fujitsu definition.

Thanks for doing that Alistair.

I put the "Ugh!" comment by it because I really don't like it. It is how
they did it in Fujitsu sample code. I've thought about it since and COBOL
types are translated to COM types by the *COM Class. (I guess MF have a
similar facility. Part of this exercise is to investigate that.) There IS a
COM type of VBOOL so it is possible that using a 16 bit (VB TypeBoolean)
with all bits set might have the same effect. Could you possibly try it
replacing the stupid PIC 1 field as: 01 COMTrue pic s9(4) comp value -1. ?

Failing that, it is also possible that the new spreadsheet is set to visible
by default and this action may not be required anyway...
>>
>> I don't recognize this program as being standard COBOL. If you want
>> to deal
>> with such esoterica as COM I would use the language that others use
>> to deal with
>> such matters. Specifically I don't find these constructs in any COBOL
>> document I have.
>> In general the recent attempts to make COBOL into some kind of
>> object- oriented language
>> lead us down the wrong path. I have been programming in COBOL for 42
>> years and I don't
>> recognize half the statements in the above code.
>>
>> That defeats one of the purposes of any High Level Language:
>> to be a language where programmer x can read, understand and modify a
>> program written by
>> programmer y.
>>
>> John Culleton, CPP- Hide quoted text -
>>
>> - Show quoted text -
>
> The only piece that I do not recognise as being standard cobol is the
> COMtrue bit setting. Otherwise it appears to me to be as per the last
> standard of Cobol.

I already responded to John. :-)

Thanks for your time, Alistair.

Pete.

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


From: Alistair on
On Feb 5, 11:54 am, "Pete Dashwood"
<dashw...(a)removethis.enternet.co.nz> wrote:
> Alistair wrote:
> > On Feb 3, 2:25 pm, "j...(a)wexfordpress.com" <j...(a)wexfordpress.com>
> > wrote:
> >> On Jan 18, 6:50 am, Alistair <alist...(a)ld50macca.demon.co.uk> wrote:
>
> >>> On Jan 16, 10:14 am, "Pete Dashwood"
>
> >>> <dashw...(a)removethis.enternet.co.nz> wrote:
> >>>> Does anybody use Micro Focus COBOL (any version, procedural or OO)
> >>>> to access COM or Automation server code, or even to write a COM
> >>>> compliant server module? If you do, there is a COBOL sample
> >>>> program below, written in Fujitsu OO NetCOBOL that I would be very
> >>>> interested to see "translated" to Micro Focus. It is a very small
> >>>> program and shouldn't take anyone too long.
>
> >>>> The Component Object Model provides an ideal platform for
> >>>> encapsulating functionality and making it available to other
> >>>> languages and platforms. As most of Microsoft Office is written as
> >>>> Automation servers, compliant with COM, it is also a very useful
> >>>> way to handle ACCESS, EXCEL, WORD and POWER POINT from within your
> >>>> own programs. Everything you can do manually with these packages
> >>>> can be done under program control, even from COBOL, via the COM
> >>>> interface. For example, the sample below is manipulating EXCEL,
> >>>> but it could equally well be ANY of the MS Office suite, as well
> >>>> as thousands of other COM compliant components.
>
> >>>> If you accept this request, and have no objection, I'll place both
> >>>> sets of code on the cobol21 web site with suitable background and
> >>>> acknowledgement of source. I'll also wrap your code so it can be
> >>>> used with .NET if it isn't already a .NET Assembly.
>
> >>>> Any takers?
>
> >>>> 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.
>
> >>>> Pete
>
> >>>> --
> >>>> "I used to write COBOL...now I can do anything."
>
> >>> I tried compiling this. Had to change all of the comments (MF uses
> >>> *> for comments) then ran in to the definition of ComTrue as a
> >>> problem. MF doesn't recognise the PIC and I could not find anything
> >>> to match the Fujitsu definition.
>
> Thanks for doing that Alistair.
>
> I put the "Ugh!" comment by it because I really don't like it. It is how
> they did it in Fujitsu sample code. I've thought about it since and COBOL
> types are translated to COM types by the *COM Class. (I guess MF have a
> similar facility. Part of this exercise is to investigate that.) There IS a
> COM type of VBOOL so it is possible that using a 16 bit (VB TypeBoolean)
> with all bits set might have the same effect. Could you possibly try it
> replacing the stupid PIC 1 field as: 01 COMTrue pic s9(4) comp value -1. ?
>
> Failing that, it is also possible that the new spreadsheet is set to visible
> by default and this action may not be required anyway...
>
>
>
>
>
>
>
> >> I don't recognize this program as being standard COBOL. If you want
> >> to deal
> >> with such esoterica as COM I would use the language that others use
> >> to deal with
> >> such matters. Specifically I don't find these constructs in any COBOL
> >> document I have.
> >> In general the recent attempts to make COBOL into some kind of
> >> object- oriented language
> >> lead us down the wrong path. I have been programming in COBOL for 42
> >> years and I don't
> >> recognize half the statements in the above code.
>
> >> That defeats one of the purposes of any High Level Language:
> >> to be a language where programmer x can read, understand and modify a
> >> program written by
> >> programmer y.
>
> >> John Culleton, CPP- Hide quoted text -
>
> >> - Show quoted text -
>
> > The only piece that I do not recognise as being standard cobol is the
> > COMtrue bit setting. Otherwise it appears to me to be as per the last
> > standard of Cobol.
>
> I already responded to John. :-)
>
> Thanks for your time, Alistair.
>
> Pete.
>

OK will try. I had checked to see if I could replace that one bit but
felt that the whizz-kids on this newsgroup would have beaten me to
it. :-(
From: James J. Gavan on
Pete Dashwood wrote:
> James J. Gavan wrote:
>
<snip>

>>Should I not use the following ?
>>
>>01 ls-Bool pic x comp-5.
>> 88 isTrue value 1.
>> 88 isFalse value 0.
>>
>>CALL/INVOKE "something" using xxxxx returning ls-Bool
>>
>>if isTrue
>>do this .....
>>
>>else do something else...
>>end-if
>>
>
>
> That looks fine to me, as far as it goes.
>
> (Personally, I use boolean flags as pic x because on IBM mainframes it
> generates better code (CLI - Compare logical Immediate, where the value it
> is comparing to can be stored in the same instruction, and on the Intel x86
> platform (my favourite) it is again a single compare (COMSB). Comp-5 is
> native architecture and would probably use arithmetic instructions instead.
> (I haven't checked so can't be sure...)
>
> So I would code your example above as:
>
> 01 filler pic x.
> 88 isTrue value '1'.
> 88 isFalse value '0'.
>
Brief response; that's how M/F illustrate it and comp-5 is the backbone
of their returns from invoking methods in their support classes; the
most 'common' coming back to you is pic x(4) comp-5. And should you need
to send 'positioning, i.e. 'x,y,w,h' co-ordinates for GUIs then you are
into s9(05) comp-5.

>
> We've had arguments here before about the use of 88 levels; some people love
> 'em (self included), some people don't. They're not "wrong"; it is a
> question of preference, that's all.

Not an argument with me - I LUV 'em too. See following which illustrates
both 88s and that 'dreadful' Level 78 :-

01 ErrorCode pic x(4) comp-5.
88 NoErrors value 0.
88 Error-DateFormat value 1.
88 Error-Value1 value 2.
88 Error-TwoValues value 3.
88 Error-VerifyDates value 4.
88 Error-DayName value 5.
88 Error-Separator value 6.
88 Error-MonthDisplay value 7.
88 Error-TimeDisplay value 8.
88 Error-MonthRange value 9.
88 Error-DaysRange value 10.
88 Error-DateLess value 11.
88 Error-ISO-8 value 12.
88 Error-ISO-6 value 13.
88 Error-EU-8 value 14.
88 Error-EU-6 value 15.
88 Error-NA-8 value 16.
88 Error-NA-6 value 17.
88 Error-InputValues value 18.
88 Error-ValidOutput value 19.
88 Error-NumberOfDays value 20.
88 Error-NonNumericDate value 21.
88 Error-LeapDay value 22.
88 Error-LT-1601 value 23.
88 Error-SlidingYears value 24.
88 Error-NonNumericTimes value 25.
88 Error-DayOfWeek value 26.
88 Error-Years2 value 27.
88 Error-Days3 value 28.
88 Error-StringingDate value 29.
88 Error-OutDateFormat value 30.
88 ErrorsFound value 1 thru 99.

78 MaxMessages value 30.
78 MEL value 35.
01 MessageTable-1.
05 pic x(MEL) value "Error 1 - DateFormat".
05 pic x(MEL) value "Error 2 - Value1".
05 pic x(MEL) value "Error 3 - TwoValues".
05 pic x(MEL) value "Error 4 - VerifyDates".
05 pic x(MEL) value "Error 5 - DayName".
05 pic x(MEL) value "Error 6 - Separator".
05 pic x(MEL) value "Error 7 - MonthDisplay".
05 pic x(MEL) value "Error 8 - TimeDisplay".
05 pic x(MEL) value "Error 9 - MonthRange".
05 pic x(MEL) value "Error 10 - DaysRange".
05 pic x(MEL) value "Error 11 - DateLess".
05 pic x(MEL) value "Error 12 - ISO-8".
05 pic x(MEL) value "Error 13 - ISO-6".
05 pic x(MEL) value "Error 14 - EU-8".
05 pic x(MEL) value "Error 15 - EU-6".
05 pic x(MEL) value "Error 16 - NA-8".
05 pic x(MEL) value "Error 17 - NA-6".
05 pic x(MEL) value "Error 18 - InputValues".
05 pic x(MEL) value "Error 19 - ValidIOutput".
05 pic x(MEL) value "Error 20 - NumberOfDays".
05 pic x(MEL) value "Error 21 - NonNumericDate".
05 pic x(MEL) value "Error 22 - LeapDay".
05 pic x(MEL) value "Error 23 - Century Date < 1601".
05 pic X(MEL) VALUE "Error 24 - Sliding Years > 100".
05 pic X(MEL) VALUE "Error 25 - NonNumericTimes".
05 pic X(MEL) VALUE "Error 26 - DayOfWeek <> 1 - 7".
05 pic X(MEL) VALUE "Error 27 - Years 2 = zeroes".
05 pic X(MEL) VALUE "Error 28 - Days 3 = 0 or > 366".
05 pic X(MEL) VALUE "Error 29 - StringingDate".
05 pic x(MEL) VALUE "Error 30 - OutDateFormat".

01 MessageTable-2
redefines MessageTable-1.
05 ws-Message pic x(MEL) occurs MaxMessages.

You will no doubt latch onto the above. As I 'fiddle' around with
coding, I just add to the ErrorCode table and the others, adjusting the
78s for MaxMessages and MEL.

01 MonthDays-Table-1.
05 pic 9(02) value 31.
05 pic 9(02) value 29. *> <---See check for Leap Years
05 pic 9(02) value 31. *> in method "ValidateDate"
05 pic 9(02) value 30.
05 pic 9(02) value 31.
05 pic 9(02) value 30.
05 pic 9(02) value 31.
05 pic 9(02) value 31.
05 pic 9(02) value 30.
05 pic 9(02) value 31.
05 pic 9(02) value 30.
05 pic 9(02) value 31.

01 MonthDays-Table-2
redefines MonthDays-Table-1.
05 MonthDays-Count occurs 12 pic 9(02).


I've 'thrown' in that reference to Leap Years above. I'd love to see
what COBOL 85 supporters would offer as a solution. They do the job, but
there are some really archaic examples on the Web; 'cos he thinks you
have to be a mathematician to program, you should see Judson's example.
I have a very elegant way of doing it - just by searching the Web.

Jimmy, Calgary AB
From: James J. Gavan on
Alistair wrote:
>
> As an aside, I really am beginning to hate M/F documentation. There
> doesn't seem to be any easy way of finding the stuff you really need
> to find.

Try this and see if you have any better luck :-

http://supportline.microfocus.com/documentation/books/nx51ws01/nx51indx.htm

There's an overall index for ALL the books, then indices within books.

Now I know there used to be a Personal Edition way back but it was not
anything like the N/E I use. Are you talking specifically 'Personal
Edition' or is there another called 'University Edition' - I understood
the latter to be the full McCoy - just the 22K line limit on source so
that you can't distribute it.

Where's Michael W. Can you clarify ?

Jimmy, Calgary AB