From: Pete Dashwood on
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."


From: Alistair on
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.
From: john on
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. 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
From: Alistair on
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.
>
> 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.
From: James J. Gavan on
Alistair wrote:
> On Feb 3, 2:25 pm, "j...(a)wexfordpress.com" <j...(a)wexfordpress.com>
> wrote:
>
>>
>>>> PROGRAM-ID. XLTEST.
>>>>* written by Pete Dashwood, PRIMA Computing, (NZ) Ltd. January 2010.
>>>>* (some parts loosely based on Fujitsu sample code)
>>>> ENVIRONMENT DIVISION etc......
<snip> ....

>>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.

>>>> 01 COMTrue PIC 1(1) BIT VALUE B"1". *> Ugh!!!

Well it does look like it might be specific to Fujitsu COBOL.

But what is the BIG DEAL ? I could be using Level 88's or 78's. Only
last week I spoke to a Brit who has been in Canada since 1974, three
months before me in 1975. He was using COBOL before he came across, and
while currently in an analyst role, does program in Micro Focus.

I referred him to 'Level 78's'. He corrected me, "You mean Level 88's
?". "No", I replied, "Level 78's". He wasn't aware of them - and yes Mr.
Dinosaur, (programming 42 years), the Level 78 is a Micro Focus
extension and EXTREMELY useful. I'm damn sure it would have been
proposed to the Standards Committee by M/F.

Unfortunately their rep was not the sort of personality to push for its
use. I recall from the only Standards meeting I ever visited, that was
2000 at M/F's (Newbury, Berkshire, UK) HQ. A Dutch representative, nice
guy and enthusiastic as hell pushed and pushed for some 30 minutes,
emphasized by scribbling examples on a white board - I don't recall it
now, but something about whether or not you could get away with not
having a space after a literal name - he just kept going on and on until
the dozen or so around the table gave in. (No it wasn't specifically no
space after a literal - but something just as daft that he was pushing
for :-).

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

I don't really care whether or not it is Comp- 0, 1, 2, 3, 4, 5, 6,
Comp-Sync, Comp5Length2 or Comp5Length6; I'll use what suits the
occasion. And, I can't be bothered to check, but which of the above is
so-called COBOL 85 or COBOL 2002 for that matter. I did use comp-3 and
currently use comp-5 because it works hand in glove with the way Micro
Focus have written their OO classes. (But OO 'attached' to COBOL -
that's another topic for the dinosaur to attack).

Jimmy, Calgary AB