gnucobol-users
[Top][All Lists]
Advanced

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

Re: [open-cobol-list] Which formatting convention to use?


From: Gary Cutler
Subject: Re: [open-cobol-list] Which formatting convention to use?
Date: Wed, 5 Aug 2009 20:42:43 -0400

Many IT departments that use COBOL prefer fixed over free so that cols 1-6
can be used as a change id (a tag that identifies who was the last one to
change a line of code and when.  Observe this example:

       IDENTIFICATION DIVISION.
       PROGRAM-ID. oc.
      *****************************************************************
      ** This program will control the compilation and (optionally)  **
      ** execution of an OpenCobol program.                          **
      **                                                             **
      ** Consult OC.DOC in the OpenCOBOL "Docs - GNU, OpenCobol"     **
      ** folder for information on the usage of this program.        **
      **                                                             **
      ** Check out the 'Switches' item in WORKING-STORAGE - this     **
      ** group may be used to setup default values for all these     **
      ** switches.                                                   **
      *****************************************************************
      **                                                             **
      ** AUTHOR:       GARY L. CUTLER                                **
      **               address@hidden                            **
      **                                                             **
      ** DATE-WRITTEN: June 14, 2009                                 **
      **                                                             **
      *****************************************************************
      ** CHG ID CHANGE DESCRIPTION                                   **
      ** ====== ==================================================== **
      ** GC0609 Don't display compiler messages file if compilation  **
      **        Is successful.  Also don't display messages if the   **
      **        output file is busy (just put a message on the       **
      **        screen, leave the OC screen up & let the user fix    **
      **        the problem & resubmit.                              **
      ** GC0709 When 'EXECUTE' is selected, a 'FILE BUSY' error will **
      **        still cause the (old) executable to be launched.     **
      **        Also, the 'EXTRA SWITCHES' field is being ignored.   **
      **        Changed the title bar to lowlighted reverse video &  **
      **        the message area to highlighted reverse-video.       **
      ** GC0809 Add a SPACE in from of command-line args when        **
      **        executing users program.  Add a SPACE after the      **
      **        -ftraceall switch when building cobc command.        **
      *****************************************************************
      .
      .
      .
       01  Flags.
           05 F-Compilation-Succeeded  PIC X(1).
GC0609     05 F-Complete               PIC X(1).
           05 F-EOF                    PIC X(1).
GC0709     05 F-Output-File-Busy       PIC X(1).
           05 F-LINKAGE-SECTION        PIC X(1).
           05 F-No-Switch-Changes      PIC X(1).
              88 No-Switch-Changes     VALUE 'Y'.
           05 F-Switch-Error           PIC X(1).
              88 Switch-Is-Good        VALUE 'N'.
       .
       .
       .
       000-Main SECTION.

           PERFORM 100-Initialization.
GC0609     MOVE 'N' TO F-Complete.
GC0609     PERFORM WITH TEST BEFORE UNTIL F-Complete = 'Y'
GC0609         PERFORM 200-Let-User-Set-Switches
GC0609         PERFORM 210-Run-Compiler
GC0709         IF  (S-EXECUTE NOT = SPACES)
GC0709         AND (F-Output-File-Busy = 'N')
GC0609             PERFORM 230-Run-Program
GC0609         END-IF
GC0609     END-PERFORM.
       009-Done.
       .
       .
       .
      

-----Original Message-----
From: Duke Normandin [mailto:address@hidden 
Sent: Wednesday, August 05, 2009 17:57
To: open-cobol-list
Subject: [open-cobol-list] Which formatting convention to use?

Should a COBOL noob like me be learning the language using the
traditional (strict) formatting conventions in order to learn COBOL
correctly, or is using the "free" source format OK in this
day-and-age?

I was even thinking of using some sort of template, like:

000100*A---B--+----2----+----3----+----4----+----5----+----6----+----7--
000200 ID DIVISION.
000300 PROGRAM-ID. MY_PROG.
000400 AUTHOR. Duke.
000500 DATA DIVISION.
000600 WORKING-STORAGE SECTION.
000700
000800
000900
001000
001100
001200 PROCEDURE DIVISION.
001300 MAIN-PARA.
-- 
duke

----------------------------------------------------------------------------
--
Let Crystal Reports handle the reporting - Free Crystal Reports 2008 30-Day 
trial. Simplify your report design, integration and deployment - and focus
on 
what you do best, core application coding. Discover what's new with 
Crystal Reports now.  http://p.sf.net/sfu/bobj-july
_______________________________________________
open-cobol-list mailing list
address@hidden
https://lists.sourceforge.net/lists/listinfo/open-cobol-list



reply via email to

[Prev in Thread] Current Thread [Next in Thread]