Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations gkittelson on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

How to implement methods in COBOL!

Status
Not open for further replies.

wahlers

Programmer
May 13, 2004
142
NL
How to implement methods in COBOL!

In OOCOBOL this, of course, is not a problem!
But what do we do when we don't have OOCOBOL?

Note: Keep in mind that each method can and will use different sets of linkage parameters! And the program will abend when more parameters (more 01 levels) are referenced then the caller has passed.

I came up with the following solutions for defining methods in non-OOCOBOL:



The EVALUATE solution

calling program
Code:
MOVE 'methodC' TO whichMethod 
CALL 'classProgram1'  USING
     whichMethod, workData1, workData6
called program (classProgram1)
Code:
LINKAGE SECTION.

01  whichMethod  PIC X(30)
  88  methodA  VALUE  'methodA'.
  88  methodB  VALUE  'methodB'.
  88  ...
  88  methodZ  VALUE ...

01  linkData1  PIC ...
01  linkData2  PIC ...
01  linkData3  PIC ...
01  ...
01  linkDataN  PIC ...

PROCEDURE DIVISION USING
          linkData1, LinkData2, .... linkDataN.

EVALUATE  whichMethod
,
, WHEN  methodA
,   CALL  nestedMethodA
,   USING linkData1, linkData6, linkData2
,
, WHEN  methodB
,   CALL  nestedMethodB
,   USING linkData2, linkData5, linkData7
,
, WHEN  methodC
,   CALL  nestedMethodC
,   USING linkData1, linkData6
,
,       ... 
,
, WHEN  methodLast
,   CALL  nestedMethod...
,   USING ....
, 
, WHEN OTHER
,   PERFORM  errorNoSuchMethodRoutine
,
END-EVALUATE

GOBACK
.
(some) advantages:
Standard COBOL.
Simple call structure with descriptive method name(s).

(some) disadvantages:
A lot of cumulative evaluate statements (1 for every class program).
Maintenance intensive (e.g. when a method is deprecated it should be removed from every evaluate statement concerned. When not done then eventually a lot of deprecated when's are needlessly evaluated).



The GO TO DEPENDING ON solution

calling program
Code:
MOVE 3 TO whichMethod 
CALL 'classProgram2'  USING
     whichMethod, workData1, workData6
called program (classProgram2)
Code:
LINKAGE SECTION.

01  whichMethod  PIC 9(02).
01  linkData1  PIC ...
01  linkData2  PIC ...
01  linkData3  PIC ...
01  ...
01  linkDataN  PIC ...

PROCEDURE DIVISION USING
          linkData1, LinkData2, .... linkDataN.

GO TO  methodA, methodB, methodC, ... , methodN
  DEPENDING ON whichMethod.

* fall through is same as EVALUATE WHEN OTHER condition.
  PERFORM  errorNoSuchMethodRoutine

GOBACK
.

methodA.
  CALL  nestedMethodA
  USING linkData1, linkData6, linkData2

  GOBACK
  .

methodB.
  CALL  nestedMethodB
  USING linkData2, linkData5, linkData7

  GOBACK
  .

methodC.
  CALL  nestedMethodC
  USING linkData1, linkData6

  GOBACK
  .
(some) advantages:
Standard COBOL.
Faster then the evaluate statement.
Fewer code lines needed then the evaluate statement.
Simple call structure, but method name is a number which is not descriptive and can easily be confused. You can solve this by defining an 88-level field but that needs to be coded and maintained.

(some) disadvantages:
Unconditional branch (GO TO).
Two exit points (one for each method and one after errorNoSuchMethodRoutine shared by all methods).
Called and calling program are intimately linked (dependent). You cannot(!) just add, remove or, switch methods in the 'GO TO DEPENDING ON' statement. Because this affects the caller.



The pointer solution

calling program
Code:
WORKING-STORAGE SECTION.
01  workDate1  PIC ..
01  workData6  PIC ..
01  listOfPointers.
  05  data1pointer  USAGE POINTER VALUE NULL.
  05  data2pointer  USAGE POINTER VALUE NULL.

* setPointer sets the pointer in the
* linkage section of the called program 
* to the address of the data area (workDataX).
CALL  setPointer  USING  workDate1 data1
CALL  setPointer  USING  workData6 data2

MOVE 'methodC'  TO  whichMethod
CALL 'classProgram3'  USING  whichMethod, listOfPointers
called program (classProgram3)
Code:
LINKAGE SECTION.

01  whichMethod  PIC X(30).
01  pointerList  PIC X(01).

PROCEDURE DIVISION USING  whichMethod  pointerList.

CALL  whichMethod  USING  pointerList
GOBACK
.

ID DIVISION.
PROGRAM-ID. methodC.
* method C knows how many parameters are used!
* dereference the 2 parameters using the pointerList.
...
(some) advantages:
Standard COBOL (I think???).
Fast and direct.
Fewest code lines needed in called program.
There is no maintenance needed as described for the evaluate or go-to-depending-on statement.

(some) disadvantages:
Pointer logic is seldom used.
You always need an additional step to address working-storage data.
Pointer logic can only be used in the same address space.
All codes are poluted with a lot of pointer referencing/dereferencing logic.
Increased possibility to reference random storage without being detected.
In general, more confusing (though this is a matter of getting used to and experience).



The ENTRY solution

calling program
Code:
CALL 'classProgram4methodC'  USING  
     workData1, workData6.
called program (classProgram4)
Code:
LINKAGE SECTION.

01  linkData1  PIC ...
01  linkData2  PIC ...
01  linkData3  PIC ...
01  ...
01  linkData6  PIC ...
01  ...
01  linkDataN  PIC ...

PROCEDURE DIVISION.
doNothing-JustReturn.
  GOBACK
  .

  ENTRY 'methodA' USING linkData1, linkData6, linkData2.

  CALL  nestedMethodA
                  USING linkData1, linkData6, linkData2.
  GOBACK
  .

  ENTRY 'methodB' USING linkData2, linkData5, linkData7.

  CALL  nestedMethodB
                  USING linkData2, linkData5, linkData7.
  GOBACK
  .

  ENTRY 'methodC' USING linkData1, linkData6

  CALL  nestedMethodC
                  USING linkData1, linkData6.
  GOBACK
  .
(some) advantages:
Fast and direct.
Fewest code lines (compared to the solutions given above).
Visually the cleanest structure (compared to the solutions given above).
Simplest maintenance (compared to the solutions given above). Deprecated method that are not removed are never executed (and do therefore not influence the other methods).
It resembles a method (when compared with OOCOBOL).

(some) disadvantages:
Non standard.
The number of entries is limited (however, this should be a non issue in a well designed system).



My personal preference, given the solutions above, is the 'ENTRY' solution.
 
Why not just say that one should use a COBOL compiler that support OO syntax?

Such compilers are now available for many (still not all) environments.

If your work in an environment that does NOT (yet) support an OO compiler, can you tell us which one it is? The chances are relatively good that if you spend your time "communicating with compiler vendors" on why you WANT this support instead of trying to invent psuedo-OO constructs, that your time would be "better" spent *AND* other programmers would benefit from expanded availability of this well-defined syntax and functionality.

Bill Klein
 
I have to disagree with the "maintenance" problems.

In my and others opinion, your example 1 holds as much maintenance as your Entry .

As both your exmples require the same linkage to be defined on the Main program, passing these parameters to the "method" programs causes no overhead.

so your "called" program for the first example should be translated to
LINKAGE SECTION.

01 whichMethod PIC X(30)
88 methodA VALUE 'methodA'.
88 methodB VALUE 'methodB'.
88 ...
88 methodZ VALUE ...

01 linkData1 PIC ...
01 linkData2 PIC ...
01 linkData3 PIC ...
01 ...
01 linkDataN PIC ...

PROCEDURE DIVISION USING
linkData1, LinkData2, .... linkDataN.

CALL whichMethod
USING linkData1, linkData2 .... linkDataN.


and all the whichMethod program would have the same linkage.
Just put it in a copybook and that's it.


If you don't wish to pass all variables to the calling programs then on the main program define these as global on Working, and before the call move each linkage variable to the working ones, and back when done.

e.g.

ws
01 wslinkData1 global ...

move linkData1 to wslinkData1
....
move linkDatan to wslinkDatan

call whichmethond
move wslinkData1 to linkData1
....
move wslinkDatan to linkDatan


Maintenance wise the above does never need to change unless you add/remove a linkage item.

One could also argue that the main calling progrm should not gave to declare all variables when calling a method that does not need them. That is true, and among other methods, it can be avoided by using EXTERNAL variables, in which case they wil be omitted on the call/using bits.


Even if we were to keep the evaluate solution, i consider it is hardly a "Maintenance intensive" task to comment/remove a "WHEN" group from a program when compared to the need to remove the obsolete method from the other program.

YES

you do NOT wish to keep the old method on the source, as this is just making it bigger, harder to compile, and to maintain, as whenever you are changing that program you need to make sure you don't change a method that is not used anymore.



Regards

Frederico Fonseca
SysSoft Integrated Ltd
 
To: Bill

Your remark:
"Why not just say that one should use a COBOL compiler that support OO syntax?"

Reply:
I agree!
It would be great if you can use OOCOBOL!
...see first sentence.

Your remark (repeated):
"Why not just say that one should use a COBOL compiler that support OO syntax?"

Reply (reversed):
When you have a COBOL compiler that support OO syntax one should use it!

That is: Switching to OO requires a different way of thinking. You have to think in classes and program accordingly.
Just buying the compiler is not enough and may lead to horrible systems. Some systems even worse then traditional (procedural) implementations.
I am not absolutely sure, but I have the feeling that this is one of the reasons why some shops are (still) reluctant to make the transition (besides such mondane or practical facts like transition costs).

Your remark:
"...time would be "better" spent...".

Reply:
No matter what, you also have to invest (spend) time even when you buy an OOCOBOL compiler.

The following might(!) be a dilemma:
[A) First learn how to 'think' and 'practice' OO techniques and thus avoiding abusing the extra power that comes with OOCOBOL (or abusing OO anything for that matter). Or,
Buy an OOCOBOL compiler and hope the extra power is used carefully, consciencely and sanely. Or,
[C] Buy an OO compiler and just use it in a procedural way as a better (more modern) COBOL.

Your remark:
"If your work in an environment that does NOT (yet) support an OO compiler, can you tell us which one it is?"

Reply:
In general I referred to any COBOL compiler just prior to any OOCOBOL compiler, without referring to a specific vendor. Of course COBOL-68 is also before OOCOBOL. But I implicitly assumed that nobody is using that release anymore!

To: Frederico

I used 'maintenance' for a better lack of words.
I will try to clarify...

The difference is this:
It is lines of code executed by default
(including executing dead code parts). Versus:
lines not executed at all
(not executing dead code).

Assume you have 10 methods named:
method1, method2, ... ,method10.
Assume (after some time) that:
method3 + 7 + 8 are deprecated.
Assume you are modifying the method9.

The EVALUATE statement, being common and central, will always execute dead code (the WHEN's for method3+7+8).
In contrast, using ENTRY's, you will never see any reference at all to any of the previous mentioned deprecated methods and dead code is never executed.

Of course you can and you should remove any dead code!
But this is kind like allocating dynamic storage: It is easy to allocate storage, because you always know when you need it, but it is difficult to determine when to free storage.

Similar with removing deprecated methods. There is, in practice, always a grace period. And it is usually removed after this grace period...or...it is forgotten!

Also, the ENTRY code is more localised and isolated. That is, when you remove an ENTRY there is no other live code involved.
In contrast, when you remove code from an EVALUATE statement you are in the middle of all other live methods!
You have to be just that much more extra careful.

Using EXTERNAL
This is very global data. It usually indicates a weak and unstable implementation of a system. I have never found much use for it and I have never used it. I am anxious to see a usage example...so if you have one...!

The working-storage solution as you suggested is another solution, and one I did not consider(*).
But, in practice this could mean a lot of storage consumption, or a confusing set of redefinitions or a combination of both. All in all adding extra complexity.
And the maintenance problems are the same as previously mentioned.

(*) However, I did use a similar construction once in a frequently used program used in an online environment. The system programmers complaint that the implemented system was using so much storage.
I cannot exactly remember the details (1996 or '97) but I believe the overhead was in order of 80Kb for every LUW! After modifying the storage logic it was using only around 1500 bytes of data per LUW.


Regards, Wim.
 
wahlers said:
No matter what, you also have to invest (spend) time even when you buy an OOCOBOL compiler.
Why spend time training for OO, on a pseudo-OO setup? If OO is what one requires, then <duh!>, get an OO compiler.

I agree that OO can be a handful in the wrong hands. It does take a lot of time and care to develop objects that can be used (and maintained) satisfactorily.
 
To: Dimandja


Your remark:
"Why spend time training for OO, on a pseudo-OO setup? If OO is what one requires, then <duh!>, get an OO compiler."

Reply:
I only wanted to indicate the choices:
[A] First the transition shift and (hopefully) avoid the OO pitfalls in production. Or,
Introduce OO at the same time as you make the transition.
(or, a third choice: No transition, use OO...and hope for the best...but that would be stupid!).

Anyway, I already gave a warning in the last sentence of the original first post, and I quote:
"But class-based or object-oriented techniques, when properly used, makes it so much easier. ".
With the emphasis on 'when properly used'.

The original post was intended for those programmers that are in the transition phase or do not understand what all the fuss is about OO.
I had hoped the subject title would atract those procedural (transitional) programmers.

I assume you are using OOCOBOL...then this post might not be for you. But if you are (still) interested you can read the (transitional) details in:

Also, I did take some effort to code 2 programs. One procedural program and one object based program including the same code logic as the procedural program.

And no, as suggested earlier, I am not trying to sell my coding style.
And yes, as should be clear by now, I am trying to sell the new way of thinking (classes/objects).


Regards, Wim.

p.s. The next step after OO is component technology (grouped classes) implemented by, and based on, (industry) patterns...but I have no intention to go that far for programmers that are not even used to OOA/D/P.
 
To Wim:
At least so far, I don't see any support (in this forum) for an initial "pseudo-OO" approach to learning OO before getting to OO.

By the way, I can think of two problems with your suggestion:

1) Such "objects" (methods) are NOT available to OO languages (Java, C++, C#, etc). Therefore, you must stay in a COBOL-only environment for this "learning" stage. The input that I have heard is that OO COBOL is most (*almost* exclusively) useful in a mixed OO language environment.

2) Part of learning OO "real-world" programming is learning to use class-browsers. My definition, this approach won't include such a tool.

***

Finally, on the subjec of ENTRY statements, you state,

Also, the ENTRY code is more localised and isolated. That is, when you remove an ENTRY there is no other live code involved.
In contrast, when you remove code from an EVALUATE statement you are in the middle of all other live methods!
You have to be just that much more extra careful

Actually, the ENTRY statement is VERY danderous in such cases (quite similar to PERFORM THRU / GO TO programming).
Removing the ENTRY statement does NOT remove that portion of code from the "main" program. It is entirely valid programing to PERFORM routines "under" one ENTRY statement from anywhere in the program. It is even possible to "Fall thur" to such code. It is true that a "good" coding technique of always coding an EXLICIT "exit program" (or GOBACK) statement right before the ENTRY statement will avoid "fall thru" - even this won't get rid of PERFORM logic. Furthermore, to get a CLEAN compile, one must still define all the data items in one "ENTRY" section of the code - even if that logic is never referenced at run-time.

Bill Klein
 
To: Bill

I recall I said somewhere:
"I use ENTRY for methods and for methods only".

A method is defined as follows:

ENTRY 'aMethod' USING...
CALL theNestedProgram USING...
GOBACK
.

The 3 lines together with the period (total 4 lines) is a method.
As you can see, this is including the goback.
Removing the method means removing these 4 lines as a unit.
As you can see in the following (template) structure removing a method does not affect any other code at all!
(e.g. Try to remove method 3, it is completely isolated code!)


Structure:

Code:
PROCEDURE DIVISION.
GOBACK
.

ENTRY 'method1'  USING a, b, c
CALL  nestedProgram1 USING a, b, c
END-CALL
GOBACK
.

ENTRY 'method2'  USING d, e, f
CALL  nestedProgram2 USING d, e, f
END-CALL
GOBACK
.

ENTRY 'method3'  USING g, h
CALL  nestedProgram3 USING g, h, x-ws-constant
END-CALL
GOBACK
.

ENTRY 'method4'  USING b, c
CALL  nestedProgram4 USING b, c
END-CALL
GOBACK
.

ENTRY 'method5'  USING a, b, c, f
CALL  nestedProgram5 USING c, f, b, a
END-CALL
GOBACK
.

*#####################
*
* nested programs start here!
*
*#####################

ID DIVISION.
PROGRAM-ID. nestedProgram1 COMMON PROGRAM.
...
For a full explanation I suggest you read the PDF document located at:

It describes this and much more...
It will answer a lot of your why questions.


Regards, Wim.
 
As you say, this removes the "pseudo-method" only. This means the nested program (and all its variables) are still in the program. It also means that one can FALL thru to that CALL statement - if maintenance is done on the code ABOVE the ENTRY statement.

Like PERFORM THRU with GO TO logic, this technique CAN be "safe" if everyone (always) follows the rules. However, all it takes is one set of maintenance that breaks the implied (but unenforceable by the compiler) rules to end up with hard-to-debug-and-maintain code.

***

Have you ever found SUPPORT for this type of conding technique? You certainly don't have it in this forum - and a similar thread in comp.lang.cobol received no support.

Bottom-Line:
This might seem "reasonable" (even good) to you - but others (regardless of OO, COBOL, compiler, O/S, bacgrounds) don't seem to feel it is a "good" suggestion.

Bill Klein
 
wahlers said:
And no, as suggested earlier, I am not trying to sell my coding style.
And yes, as should be clear by now, I am trying to sell the new way of thinking (classes/objects).
You can't sell ideas and not expect critiscism. Especially when the idea in question is very old (and not yours - modular programming is well known) and there now exist better and fully developed competing ideas: OO, for one.

I really tried to like this technique. But it is impractical and very retro. It creates more problems than it solves.

You are also trying to sell it as a stepping stone to OO. This stone does not lead to OO, because it is not OO, and because one will not learn OO by pretending to code OO. You need to do it, as in get an OO compiler and do it.

I don't see how anyone can learn OO by struggling with a non-OO compiler. Lots of pain, but no gain.

Dimandja
 
To: Bill

As you say, this removes the "pseudo-method" only. This means the nested program (and all its variables) are still in the program. It also means that one can FALL thru to that CALL statement - if maintenance is done on the code ABOVE the ENTRY statement.

Reply:
There is no code above the entry statements.
By just removing the 'ENTRY...GOBACK' lines you will never fall thru.
Yes, all the variables may still be in the program (if not also removed). But the dead code is really dead! It will never be executed again. Of course(!) it is not a good idea to leave dead code in the program! However, in practice dead code is everywhere, even in the standard Java library.

However, all it takes is one set of maintenance that breaks the implied (but unenforceable by the compiler) rules to end up with hard-to-debug-and-maintain code.

Reply:
Partly true! Of course, nobody can prevent anybody to do strange things. However, I do not rely on the maintainer! It is very simple to automatically check that there is a 'GOBACK' statement before (yes before!) every ENTRY. Thus; ENTRY - ENTRY - GOBACK does not exist. And no sections or paragraphs can exist between ENTRY and GOBACK. These are the only 2 rules. Very simple! Easily checked (automatic of course!).

Have you ever found SUPPORT for this type of conding technique? You certainly don't have it in this forum - and a similar thread in comp.lang.cobol received no support.

Reply:
My collegues and I have coded succesfully(!) for a Norwegian bank and later reused many classes for a Swedish oil company. Now bank business and oil business are 2 different things. But a great part of the code was so generic (see PDF document) that it could easily be implemented. Did I receive support on any of the threads? No! But I only mentioned it 3 days ago. And so far I haven't spoken to anyone who actually read the PDF document or asked a question about any aspect of the 2 programs involved (except one).

Bottom-Line:
This might seem "reasonable" (even good) to you - but others (regardless of OO, COBOL, compiler, O/S, bacgrounds) don't seem to feel it is a "good" suggestion.

Reply:
A forum implies a wide variaty of participants. Some are only interested in good code fragments, others are their for problems/solutions, some for the gossip or curiosity. I just presented some food for thoughts.
Of course this is much bigger then your 20 lines or so coding problem. And people tend to rush to a conclusion before they really looked through it all.
It also gives a distored view if only one (or 2) persons speak their minds in a charade of replies. I don't say this bad but, in general, you get influeced by what you see most. This is a good thing!...except when it just comes from one person. I am just trying to reach the greatest audiance. What you (not you personally, but you the reader) do with it is up to you.
I appreciate your criticism and I tried to answer you to the best of my abilities...then again it is very difficult to show the complete picture. A part is described in the PDF document. This is only a part and that is already 70 pages!

Bottom line: Nobody will ever become interested if you never discuss it.


Regards, Wim.
 
Wim,

I did read your PDF document and my opinion is still the same.

I have been developing reusable COBOL code for the last 16 years, some originally written in COBOL-74, so I know very well what I am speaking about.
I don't do it anymore, but there was a time where my code would need to run in both COBOL 74 and 85, from different manufacturers, so you learn to do very well compartmentalized code, and separating all business logic from screen i/o and from file I/O. So in 1990 I already had a three-tier design on all my apps (four if you consider that all printing was also an independent module).

As for your code, apart from the style bits I don't like, is clean, but would not work on three of the compilers I use (ENTRY is not available on them), so there is no point in discussing the good/bad points of ENTRY.

As for your posts, my main comments were related to the fact that you were addressing your code as being object oriented (changed afterward to object/class based), and as others have confirmed, this was just not correct.


Regards

Frederico Fonseca
SysSoft Integrated Ltd
 
To: Dimandja

Again, it is not about OO!
It is directed to procedural programmers who are not yet in their transitional phase and only work with a procedural programming language.
Thinking in objects and defining classes is a good base for writing generic code.
I just provided a way (and there is more then one way!) in which you can achieve this in a procedural environment. That is all!
More details are written in the PDF document I mentioned.


Regards, Wim.
 
To: Frederico

I did read your PDF document and my opinion is still the same.

Reply:
Thank you, and I respect your opinion!

I don't do it anymore, but there was a time where my code would need to run in both COBOL 74 and 85, from different manufacturers, so you learn to do very well compartmentalized code, and separating all business logic from screen i/o and from file I/O. So in 1990 I already had a three-tier design on all my apps (four if you consider that all printing was also an independent module).

Reply:
The paper was obviously not intended for you.
The way you described it is, in my opinion, the correct way.
You be surprised, almost 15 years later, how monlithic some other environments can be. I am not talking about old ones but recent ones! I hpe they will wake up...but they are at least 15 years behind.

As for your code, apart from the style bits I don't like, is clean, but would not work on three of the compilers I use (ENTRY is not available on them), so there is no point in discussing the good/bad points of ENTRY.

Reply:
Very true! ENTRY is non standard (you use 3 compilers?).
The prefer the pointer logic approach (more generic) but that scares the hell out of most people! By the way, this was not used within my team...ENTRYs were used. But I did write a generic code were you could pass between 1 and 99 working-storage fields and load them into a pointer area (by the way 99 is a lot! The most I ever used was just 9...as far as I can remember).

As for your posts, my main comments were related to the fact that you were addressing your code as being object oriented (changed afterward to object/class based), and as others have confirmed, this was just not correct.

Reply:
This comment I have to strongly deny!
I changed just one sentence because it was confusing only!
It was written similar to the following:
...object based or object oriented techniques can be...
The or in this sentence was in the semantical meaning of exclusive or. However, in the Dutch language, and as far as I know in the english language as well, there is no distinction between the exclusive or and inclusive or.
This distinction was very clear for me but not for the reader. That and only that was the reason why I changed that single line!
You read my paper...I wrote the same distinction in the paper (where it says object-based versus object-oriented).

Can I conclude by saying:
1. That the sugestion of using ENTRYs in your environment is irrelevant because ENTRY is not supported.
2. You will never use them because they are not generic.
3. You code generic and not monolithic. Which makes perfect sense to me!
3. (assumption) By now you are object-oriented(?).
(the last being more a question then a statement)


Regards, Wim.

p.s. about the style bit. First I am not a writer. Secondly english is not my native language. Thridly I have a small dyslectic problem (though minor...e.g. I cannot find a word on a screen...have to use a finger for that...don't see that I have forgotten complete words...have to preview my replies about 4 times and correct them before sending...and even then...)
 
Wim: "It is directed to procedural programmers who are not yet in their transitional phase and only work with a procedural programming language."

What "transitional phase" are they supposed to be in? You really believe all programmers are aspiring to something more than what they are doing now? You don't think "procedural" methodologies are good enough for their business requirements? Why should anyone have to go into "transition"? For that matter, why should any programmer strive to code OO-based or client-based stuff, when there are no business requirements for it (much less a compiler), when good old modular will do nicely?

It looks to me like you are underestimating the capabilities of programmers in general, because you are prescribing remedies where they are not warranted. If I hear you correctly, you are saying "learn my stuff, before you venture into OO". I am saying your style has no obvious benefit: it pretends to be either OO-based or class-based, when, calling it "modular" will suffice.

Trust me, there are better ways to learn OO; I think this is not even close. I explained my views in the other related thread, and will not rehash them here.

Dimandja
 
To: Dimandja

Let me rephrase that...

There will always be procedures that are better being done by batch or any other long existing technique (but therefore not obsolete technique!).
OO is just an extention of all existing techniques.
However, there is no escape to OO.
You either adapt or stay foot wherever you are.
I think the better choice is to adapt.
Some choose not too and that is fine.

Some of those who want to adapt, expand their horizons, or whatever you call it are not in the fortunate position of having the required resources. Some are still in doubt. And, I hope you agree, if you have never done anything OO then it can be very difficult to think in terms of classes, inheritance, polymorphism, and things like that. This has nothing to do with underestimating capabilities. It is just a different mind set. Now maybe the word "transition" was ill chosen. But, by transition, I do mean the mind shift to the OO way of thinking.
I just tried to provide an alternative (based on COBOL code) that can be used using a procedural environment.

Don't confuse showing an alternative with enforcing an alternative!

The PDF paper mentioned is based on a multi-year project (almost three years, 1996-1999) for three different customers in 2 different countries. It worked for us, succesfully. I made the effort to share my knowledge. If not you then maybe somebody else can use (some of) my experiences. That is all...no attack to anybody or anything...just sharing something that works.


Regards, Wim.
 
Wim,

I use the following compilers currently.

RM/COBOL
ACUCOBOL
MICROFOCUS COBOL
FUJITSU COBOL
IBM COBOL/400 (AS400)
IBM ILE-COBOL (AS400)
IBM COBOL for Aix

When I mentioned your style I was not addressing language issues, or ways of expressing yourself. I don't have English as my primary language either.

I was referring to the fact that you use (and abuse on my personal opinion) of commas for alignment
PERFORM ...
, PERFORM setJumpSizeAndUpperLimit
,
, PERFORM ...
, ,
, , PERFORM getKeyOffsetValues
, ,
, , CALL orderEntries USING
, , , tableEntryLength
, , , keyLength

I personally dislike this but this is a "style" issue, so it's not right or wrong.



Can I conclude by saying:
1. That the suggestion of using ENTRYs in your environment is irrelevant because ENTRY is not supported.
It's not relevant in some, but would not be used.
2. You will never use them because they are not generic.
They would be used if there was a very valid reason to do it. Haven't found one yet.
3. You code generic and not monolithic. Which makes perfect sense to me!
Yes. Loads of modules that can or not be used together.

3. (assumption) By now you are object-oriented(?).
Yeap!!
but only on a few projects (COBOL wise). I also develop in other languages.


Regards

Frederico Fonseca
SysSoft Integrated Ltd
 
To: Frederico

You dislike my ,,,,,,,,,,,,,, :)

You are not the only. I already mentioned to somebody (I forgot who) that I really need them otherwise it is more difficult for me to read (or follow) my own code.
I am not talking about difficult or deeply nested structures but just reading sentences...


Regards, Wim.
 
Should anyone care,

The use of ",," (with no intervening spaces) is NOT equivalent to a space in any ANSI/ISO conforming compiler (any version of COBOL Standard).

The Standard (past and present) explicitly state that a comma MUST be followed by one (or more) spaces (or end of line) to be considered a "separator comma".

Bill Klein
 
Wim said:
OO is just an extention of all existing techniques.
However, there is no escape to OO.
You either adapt or stay foot wherever you are.
Just to make conversation, I believe OO is but one of the extensions to known techniques.

For example, it is an extension of modular programming; but it is definitely not an extension of distributed programming. (In case you are wondering, I have used both techniques in my work.)

Not learning OO is not the end of the world. Other techniques are more a-propos for the work lots of programmers are required to do. OO is only an option that may or may not be appropriate for the work at hand.

In my experience OO is more at home in integrated and single user environments such as user interfaces, while distributed programming is better in applications that are designed to accommodate large unknown numbers of users such as servers in online applications.

Furthermore, both those techniques are often used in the same applications, with OO playing mainly in the foreground. Meaning that a programmer who codes servers has an interest in staying away from OO, while UI programmers have no use for distributed techniques. But they process and exchange information in parts of the same application.

OO is not needed for everyone.

Dimandja

 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top