Results 1 to 10 of 10

Thread: COBOL Tutorial

  1. #1
    Senior Member
    Join Date
    Dec 2001
    Posts
    590

    Post COBOL Tutorial

    OK, now why am I doing a COBOL tutorial?? I got no idea. It's an old language and many of today's newer languages can do the things it does and even more. So, basically, I'm doing it cos I just finished an assignment on it and it's fresh in my mind so I though I'll just write about it...it won't hurt. Keep in mind, there are many large legacy systems that use COBOL, so it is good to know it. Like for instance today, I had an interview with the National Australia Bank about a placement there and they said their main system is coded in COBOL and they have to use it.

    So anyways, enough crap, on with this kinda crappy COBOL tutorial - hopefully some of you will actually try do it...or not... (mind you, I only know the basics, so hopefully I can pass them on to you)

    OK, first of all, in COBOL you have strict rules on where your code is - ie. what position on a line. (NOTE: This is for COBOL 85)

    -each line can only have 80 characters
    -only use positions 7 thru to 72
    -position 7 is for special purpose - ie. * marks comment
    -position 8 thru 11 is for division names, section names, paragraph names, etc
    - position 12 thru to 72 is for all other things - the actual code (if statements, variables, etc...)

    division names:
    -------------------
    4 divisions - identification division (used for program ID, author name, date written, etc.)
    - environment division (used to state which files - if any - you use)
    - data division (use to declare variables)
    - procedure division (the actual coding)

    ok - let me simply start by giving you code from a sample program

    0001 IDENTIFICATION DIVISION.
    0002 PROGRAM-ID.
    0003 SAMPLE1.
    0004
    0005 ENVIRONMENT DIVISION.
    0006
    0007 DATA DIVISION.
    0008 WORKING-STORAGE SECTION.
    0009 01 USER-NAME PIC X(20).
    0010 01 MSG PIC X(17) VALUE 'WELCOME TO COBOL!'.
    0011
    0012 PROCEDURE DIVISION.
    0013 000-GREETING.
    0014 DISPLAY 'ENTER YOUR NAME'
    0015 ACCEPT USER-NAME
    0016 DISPLAY 'HELLO ', USER-NAME, MSG
    0017 STOP RUN.

    OK, this program simply accepts your name and then prints a welcome message with your name in it.

    -the numbers along the left side are the line numbers
    -as you can see 'ENVIRONMENT DIVISION' is there, but nothing is under it. I just put it there to show you where it goes, however, if it is not in use, you can exclude it.
    -under 'DATA DIVISION' you have 'WORKING-STORAGE SECTION'. This is where all your variables go.
    -PIC (PICTURE) defines what the variable is. Here are some examples:

    PIC X. --this would be a single character which can store anything (eg. '1', 'W', '%')
    PIC 9. --this is a numeric field, which stores one number (eg. 3, 6, 8)
    PIC X(10). -- this would store a string 10 chars long (eg. 'HELLO MATE', 'DI&$9DHH3K')
    PIC 9(10). --this would store numeric field 10 digits long (eg. 1234567890, 7483909847)

    I think you get the point with the PIC.

    OK, you'll notice the '.' (full-stops) everywhere. You basically put them at the end of division, section and paragraph names. You also put them at the end of each variable defined. It is confusing, but once you get the hang of it - it'll be sweet.

    After the 'PROCEDURE DIVISION' you'll notice '000-GREETING'. This could have been 'MESSAGE' or '345-HELLO'. It is just a paragraph name and I used 000 so that if I had like 10 pages of code and 8 different paragraphs, I can easily find where 000 is, as it would be in order. (for example, next paragraph could be 001-VALIDATE or something).

    In the 'PROCEDURE DIVISION' you then have:
    'DISPLAY...' - This does what it says - displays 'ENTER YOUR NAME' on the screen.
    'ACCEPT...' - This basically is a prompt for the user to enter their name (not difficult is it!!)
    ...and I'm sure you can understand what the lines below it do.

    You'll notice at the end of STOP RUN. (which ends the program) - we have a full-stop. You always have a full-stop when a paragraph finishes. So this ends the 000-GREETING paragraph.

    OK, well, there it is. I hope some of you actual take time to look at it. The compiler that I use is RMCOSTER. If you would like it, feel free to contact me and I will inform you on how you can get it. My contacts are any of the following:

    ICQ: 16488150
    AIM: hot ice GLS
    e-mail: hot_ice@antionline.org

    If you have any questions, feel free to ask or simply post in this thread.

    Greg
    \"Do you know what people are most afraid of?
    What they don\'t understand.
    When we don\'t understand, we turn to our assumptions.\"
    -- William Forrester

  2. #2
    hot_ice very cool, and very basic tutorial on Cobol. I've been taking Cobol at school going on my second semester of it, thank you I do feel very privledged. I would just like to add to it.

    The environment divsion is very Important. This is where you put your select, and assign statements. Lets say you want to print somthing to a file, or get input from another file. This is where I put that kinda thing.

    IDENTIFICATION DIVSION.
    PROGRAM-ID. TUTORIAL.
    AUTHOR. freeOn.

    That's all I'm going to do in the identification division.
    I go on the the environment division.


    ENVIRONMENT DIVISION.
    INPUT-OUTPUT SECTION.
    FILE-CONTROL.
    SELECT TUTORIAL-FILE

    ASSIGN TO
    'C:\TUTORIAL.DAT'
    ORGANIZATION IS LINE SEQUENTIAL.

    SELECT PRINT-FILE
    ASSIGN TO
    'C:\TUTORIAL.TXT'

    Ok that's how I would do it. The first Select I do is where my file is at. In Cobol you need to tell it exactly where you file is at. Know if you where just going to print to the screen. You wouldn't need to do your Environment divsion. But this is still a good way. After you tell Cobol where your file is at you then assign it's print file. The print file is a txt. This will tell cobol to create a tutorial.txt and it will put all are new processed information in it .

    DATA DIVISION.
    FILE SECTION.
    FD TUTORIAL-FILE.
    RECORD CONTAINS 2 CHARACTERS.
    DATA RECORD IS PRINT-LINE.

    01 TUTORIAL-RECORD.
    05 ENTER-YES PIC X(1).
    05 ENTER-NO PIC X(1).

    FD PRINT-FILE
    RECORD CONTAINS 80 CHARACTERS
    DATA RECORD IS PRINT-LINE.

    01 PRINT-LINE PIC X(80).

    Ok that was my data divsion.



    Most of the time when you get output, and do the PIC. You do it in a named line. Such as

    WORKING-STORAGE SECTION.

    01-Heading Line 1.
    FILLER PIC X(11) VALUE 'COBOL IS COOL'.
    FILLER PIC X(10) VALUE FILLER.
    FILLER PIC X(2) VALUE 'OR'.
    FILLER PIC X(1) VALUE FILLER.
    FILLER PIC X(2) VALUE 'IS'.
    FILLER PIC X(10) VALUE FILLER.
    FILLER PIC X(11) VALUE 'COBOL LAME?'

    . Basically it's going to print out like this.
    COBOL IS COOL OR IS COBOL LAME?

    The filler is nothing. Used as spaces inbetween values. Well of course my heading line will go in Working Storage section. Which is in the Data Division. It's not just going to print out that, you have to go to the procedure division.

    PROCEDURE DIVISION.
    PREPARE-TUTORIAL-REPORT.
    OPEN INPUT TUTORIAL-FILE
    OUTPUT PRINT-FILE.
    READ TUTORIAL-FILE
    END-READ.
    PERFORM WRITE-HEADING-LINE
    CLOSE TUTORIAL-FILE
    PRINT-FILE.
    STOP-RUN.

    That was aka, your mainline. It shows the whole process of what your program is going to do.
    Notice the PERFORM WRITE-HEADING-LINE., It's not the same as the one in working storage.
    It what your going to do next.

    WRITE-HEADING-LINE.
    MOVE HEADING-LINE-1 TO PRINT-LINE.
    WRITE PRINT-LINE AFTER ADVANCING 1 LINE.

    That's it this program should create a tutorial.txt file and write to it.

  3. #3
    Senior Member
    Join Date
    Dec 2001
    Posts
    590
    Good stuff freeOn.

    The thing about COBOL which I find very good is that it is excellent in handling files. (Mind you, I've only been doing it for a month or two - so I'm talking about simple text files). I got this opinion, cos I also know java and when working with files in java, you have to code so much to prevent the program from crashing. You have to catch exceptions here and there and it is much more messy. With COBOL, it basically takes care of almost everything. The only thing you have to check for is EOF (End-of-File), which is very very easy to do.

    example (snippet of code):

    READ RECORD-FILE
    AT END MOVE 'YES' TO EOF
    END-READ

    And that's it. Very simple.

    Greg
    \"Do you know what people are most afraid of?
    What they don\'t understand.
    When we don\'t understand, we turn to our assumptions.\"
    -- William Forrester

  4. #4
    Junior Member
    Join Date
    Dec 2001
    Posts
    23

    Thumbs up

    I've no additional information to add to this thread, I would just like to say thanks!
    Nice job!
    Keep up the good work!

  5. #5
    Senior Member
    Join Date
    Oct 2001
    Posts
    107
    I am using the Deskware and Acubol compilers (windows). Anyway, whenever I run the program on one, the box it pops up in closes after a second. The other one continuously displays the number and then causes a page fault. Anyway to fix that?
    IDENTIFICATION DIVISION.
    PROGRAM-ID. MOOSE.
    ENVIRONMENT DIVISION.
    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 MOOSE PIC 999 COMPUTATIONAL.
    PROCEDURE DIVISION.
    MOVE 846 TO MOOSE.
    DISPLAY MOOSE.

  6. #6
    Senior Member
    Join Date
    Dec 2001
    Posts
    590
    whenever I run the program on one, the box it pops up in closes after a second.
    Does this program run in DOS? If so, open up a DOS window first, then run the program from the DOS window, then it won't close after it is ran.

    IDENTIFICATION DIVISION.
    PROGRAM-ID. MOOSE.

    ENVIRONMENT DIVISION.

    DATA DIVISION.
    WORKING-STORAGE SECTION.
    01 MOOSE PIC 999.

    PROCEDURE DIVISION.
    000-MAIN-MODULE.
    MOVE 846 TO MOOSE
    DISPLAY MOOSE
    STOP RUN.

    When I ran your code exactly in my compiler (RMCOSTAR), it did not work. The things I changed are:

    *removed COMPUTATIONAL after 01 MOOSE PIC 999 - I don't know why, but it just didn't like it for me, so I removed it - it's only use is to improve speed I think, so for a simple prog like this, it really isn't necessary.

    *after the PROCEDURE DIVISION is started, you need to name it before you start doing stuff - so I just named mine 000-MAIN-MODULE.

    *removed full-stops after MOVE 846 TO MOOSE and DISPLAY MOOSE

    *added to the end STOP RUN.

    (NOTE: in the PROCEDURE DIVISION, you only have full-stops at the end of the procedure name (000-MAIN-MODULE) and the end of the procedure (this case STOP RUN).

    Also, if you would like my compiler, e-mail me at hot_ice@antionline.org - it's not even 1MB.

    Hope this helps,
    Greg
    \"Do you know what people are most afraid of?
    What they don\'t understand.
    When we don\'t understand, we turn to our assumptions.\"
    -- William Forrester

  7. #7
    Senior Member
    Join Date
    Oct 2001
    Posts
    107
    Thanks for the compiler. I appreciate your time spent. Also, could you tell me what benefit AO points are?

  8. #8
    Senior Member
    Join Date
    Dec 2001
    Posts
    590
    Basically, people give you positive AntiPoints if they think that your post was really helpful/good/enjoyable/etc...
    People give out negative AntiPoints if they think your post was totally irrelevent/bad/disgraceful/rude/etc...

    As you can see under my name, I don't give out much AntiPoints. I've only given out a few positive ones, no negative ones yet. I only give them out if I think someone is really great informative post - I don't like the idea of just dishing them out for every post I read.

    Greg
    \"Do you know what people are most afraid of?
    What they don\'t understand.
    When we don\'t understand, we turn to our assumptions.\"
    -- William Forrester

  9. #9
    I'm completely lost by your talk about COBOL, but I really liked and enjoyed your tutorial, I'm learning C++, I think, lol..And it is hard and frustrating, I alwasy wanted to see what the older laguages looked like. go to the roots.

  10. #10
    Senior Member
    Join Date
    Sep 2001
    Posts
    535
    hey this was great man hot_ice though it was a small tut but was helpful ...
    keep posting..

    intruder..
    A laptop, internet connection and beer.

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •