In <201302201529.55146.jlturr...@centurytel.net>, on 02/20/2013
at 03:29 PM, Leslie Turriff said:
>All issues with level numbers and usage clauses may be quickly
>resolved by looking at the COBOL Language Reference manual
>(unless one has an aversion to reading it).
Or, more likely, the syn
In
,
on 02/20/2013
at 09:15 AM, Thomas Berg said:
>Do you in this regard prefer, e g, that:
>01 NAME1 PIC X.
>88 ONE VALUE '1'.
>88 ZERO VALUE '0'.
>- instead be:
>01 NAME1 PIC X.
>WHEN VALUE '1' SETTRUE ONE.
>WHEN VALUE '0' SETTRUE ZERO.
>?
On 20 Feb 2013 13:37:40 -0800, in bit.listserv.ibm-main Leslie wrote:
>On Wednesday 20 February 2013 02:15:51 Thomas Berg wrote:
>> > It's not the features that are bad in those instances, but rather the
>> > syntax for requesting the features; that syntax is about as far from
>> > the purported E
In my previous post
= addr(s) ;
is properly
sp = addr(s) ;
John Gilmore, Ashland, MA 01721 - USA
--
For IBM-MAIN subscribe / signoff / archive access instructions,
send email to lists...@listserv.ua.edu with the message: INFO
No, unlike C, which has only pointers to functions, PL/I has procedure
variables, which may of course be based, pointed to.
A pointer, inclusive of a procedure pointer, should be just a pointer,
no different from a pointer to an aggregate or scalar. What that
pointer points to may of course have
On Wed, 20 Feb 2013 21:19:16 -0500, John Gilmore wrote:
>
>pointer
>procedure-pointer
>program-pointer
>
>are the poster children for this dubious practice. I know what the
>differences among tgherm are, but if pointer had not been misconceived
>in the beginning they would have been unnecessary.
Some things improved when the future of COBOL was wrested from
Codasyl, and some did not. We still have the proliferation of
distinctions among entities that ought not to be distinguished,
distinctions without substantive differences.
The three entities
pointer
procedure-pointer
program-pointer
t;To: IBM-MAIN@LISTSERV.UA.EDU
>Sent: Wednesday, February 20, 2013 2:29 PM
>Subject: Re: SV: SV: SV: Article for the boss: COBOL will outlive us all
>
>On Wednesday 20 February 2013 02:15:51 Thomas Berg wrote:
>> > It's not the features that are bad in those instances, but r
On Wednesday 20 February 2013 02:15:51 Thomas Berg wrote:
> > It's not the features that are bad in those instances, but rather the
> > syntax for requesting the features; that syntax is about as far from
> > the purported English-like character of COBOL as you can get.
> >
> > >I can't immediately
> -Ursprungligt meddelande-
> Från: IBM Mainframe Discussion List [mailto:IBM-MAIN@LISTSERV.UA.EDU]
> För Shmuel Metz (Seymour J.)
> Skickat: den 20 februari 2013 01:20
> Till: IBM-MAIN@LISTSERV.UA.EDU
> Ämne: Re: SV: SV: Article for the boss: COBOL will outlive us all
In
,
on 02/18/2013
at 02:48 PM, Thomas Berg said:
>Do you imply that these features is promoting/helping obfuscating ?
It's not the features that are bad in those instances, but rather the
syntax for requesting the features; that syntax is about as far from
the purported English-like charact
On Monday 18 February 2013 23:20:46 Ed Gould wrote:
> Most places I have worked the use of ALTER was banned in the
> standards manual.
>
> Ed
Not this place; my "mentor" chastised me for using structured methods
(he
didn't understand it). :-P
Leslie
-
Most places I have worked the use of ALTER was banned in the
standards manual.
Ed
On Feb 18, 2013, at 7:45 PM, Leslie Turriff wrote:
On Monday 18 February 2013 05:16:45 Thomas Berg wrote:
(I really hate the ALTER command.)
Fortunately I haven't seen this the last +20 years or so. Anf if
On Monday 18 February 2013 15:57:12 Clark Morris wrote:
> On 18 Feb 2013 08:30:24 -0800, in bit.listserv.ibm-main you wrote:
> >The plumbing needed to implement Paul Gilmartin's suggestion is more
> >complex than he perhaps implies it to be. An implementation is
> >straightforward in PL/I, e.g.,
>
On Monday 18 February 2013 05:16:45 Thomas Berg wrote:
> > (I really hate the ALTER command.)
>
> Fortunately I haven't seen this the last +20 years or so. Anf if I had I
> would have strangled the programmer... :)
I had one at my last application programming job last year. (They
never
On 18 Feb 2013 08:30:24 -0800, in bit.listserv.ibm-main you wrote:
>The plumbing needed to implement Paul Gilmartin's suggestion is more
>complex than he perhaps implies it to be. An implementation is
>straightforward in PL/I, e.g.,
>
>declare infile file record sequential buffered ;
>...
>declar
The plumbing needed to implement Paul Gilmartin's suggestion is more
complex than he perhaps implies it to be. An implementation is
straightforward in PL/I, e.g.,
declare infile file record sequential buffered ;
...
declare read_file aligned bit ; /* boolean */
...
on endfile(infile) read_infile
Epigonoi and its descendents are good words. The insistent question
| Perché gli Epigoni dovrebbero essere inferiori ai progenitori?
has been repeated for two odd millenia now, but the pejorative sense
of these words fills a need, and I think that the best response to
this question is that desce
On Mon, 18 Feb 2013 09:23:52 -0600, John McKown wrote:
>A friend of mine had something similar. He did a
>
>PERFORM UNTIL FILE-EOF
> READ ... AT END SET FILE-EOF TO TRUE.
> IF NOT FILE-EOF THEN ...
>the rest of the program
> END-IF
>END-PERFORM
>
In any wisely designed language, READ is a
A friend of mine had something similar. He did a
PERFORM UNTIL FILE-EOF
READ ... AT END SET FILE-EOF TO TRUE.
IF NOT FILE-EOF THEN ...
the rest of the program
END-IF
END-PERFORM
--
For IBM-MAIN subscribe / signoff / arc
On Mon, 2013-02-18 at 09:26 -0500, John Gilmore wrote:
> This notion was later reified by Dijkstra's epigoni into
> an interdiction: all GOTOs as bad in all circumstances.
"Epigone", what a great word.
In my undergraduate days, in the immediate wake of Dijkstra's CACM
letter, acquaintances of min
GOTO DEPENDING certainly has its uses; and this usefulness can serve
as the anchor for a more general observation.
Dijkstra's original GOTO paper did not interdict them; it suggested
that thickets of GOTOs were undesirable and set out the metric that
the quality of a program is inversely related t
On Sun, 2013-02-17 at 15:54 -0600, Leslie Turriff wrote:
> (I really hate the ALTER command.)
Yes, but GOTO DEPENDING (branch tables) can be quite useful for e.g.
state machines.
--
David Andrews
A. Duda & Sons, Inc.
david.andr...@duda.com
---
> -Ursprungligt meddelande-
> Från: IBM Mainframe Discussion List [mailto:IBM-MAIN@LISTSERV.UA.EDU]
> För Shmuel Metz (Seymour J.)
> Skickat: den 18 februari 2013 13:07
> Till: IBM-MAIN@LISTSERV.UA.EDU
> Ämne: Re: SV: Article for the boss: COBOL will outlive us all
>
> In
> >,
> on 02/16/
> -Ursprungligt meddelande-
> Från: IBM Mainframe Discussion List [mailto:IBM-MAIN@LISTSERV.UA.EDU]
> För Leslie Turriff
> Skickat: den 17 februari 2013 22:54
> Till: IBM-MAIN@LISTSERV.UA.EDU
> Ämne: Re: SV: SV: Article for the boss: COBOL will outlive us all
>
&g
On 17 Feb 2013 14:01:41 -0800, in bit.listserv.ibm-main you wrote:
>On Sunday 17 February 2013 12:47:16 Thomas Berg wrote:
>> Some suggestions:
>>
>> * GO TO's from in the middle of one SECTION into the middle of another.
>> And then GO TO back again depending on a "switch"... * Programs with nes
On 17 Feb 2013 11:03:08 -0800, in bit.listserv.ibm-main you wrote:
>Thomas,
>
>I see your point ...writing in Cobol , because I must to support a product, I
>have used a bunch of assembler routines, we are converting to C
You definitely should read the latest COBOL manuals thoroughly to see
which
On Sunday 17 February 2013 12:47:16 Thomas Berg wrote:
> Some suggestions:
>
> * GO TO's from in the middle of one SECTION into the middle of another.
> And then GO TO back again depending on a "switch"... * Programs with nested
> PERFORMS (*only* PERFORMS!) in maybe 7 levels ending in a CALL of a
Additionally, String and Unstring are very powerful verbs in Cobol. Good
parsing is a essential when looking at data, some akin to Rexx would be great
in Cobol...C you can use tokens
Scott ford
www.identityforge.com
Tell me and I'll forget; show me and I may remember; involve me and I'll
unde
The pointer addition to Cobol, you use very effectively. I have queried the CVT
...for various fields successfully.
Scott ford
www.identityforge.com
Tell me and I'll forget; show me and I may remember; involve me and I'll
understand. - Chinese Proverb
On Feb 17, 2013, at 3:39 PM, Scott Ford
The pointer addition to Cobol, you use ver effectively. I have queried the CVT
...for various fields successfully.
Scott ford
www.identityforge.com
Tell me and I'll forget; show me and I may remember; involve me and I'll
understand. - Chinese Proverb
On Feb 17, 2013, at 2:45 PM, John Gilmore
Thomas Berg's notion that COBOL is hard to obfuscate is less true than
it once was.
REDEFINES has always had its obfuscatory uses; but the availability of
pointers now makes data-type punning easy in a language that has no
tradition of its appropriate, in-good-taste use.
Let me repeat myself. CO
Thomas,
I see your point ...writing in Cobol , because I must to support a product, I
have used a bunch of assembler routines, we are converting to C
Scott ford
www.identityforge.com
Tell me and I'll forget; show me and I may remember; involve me and I'll
understand. - Chinese Proverb
On Feb
Some suggestions:
* GO TO's from in the middle of one SECTION into the middle of another. And
then GO TO back again depending on a "switch"...
* Programs with nested PERFORMS (*only* PERFORMS!) in maybe 7 levels ending in
a CALL of another module.
* Field name (variable) in (e g) MOVE statemen
34 matches
Mail list logo