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 IamaSherpa on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

problem with perform

Status
Not open for further replies.

stilleke

Technical User
May 28, 2004
2
BE
Hi,
Cobol is very new to me, and I still have problems with perform.

The purpose of this program is that it shows you the maximum and average temperature of each day, and the maximum temperature for that week.

But when I run this program, it won't stop when I type -1 (scope-terminator) for the day, and it always gives the temperature for monday. I really don't see what I'm doing wrong!

Can anyone help me, please?
Thx

Code:
IDENTIFICATION DIVISION.
       PROGRAM-ID. examen.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 temperature.
        03 wday occurs 7.
         05 dayname pic x(10).
         05 max pic s99 value -99.
         05 sum pic s999 value 0.
         05 counter pic 99 value 0.
         05 av pic s99v9.
       77 daynumber pic s9.
        88 number value 1 thru 7.
       77 temp pic s99.
       77 hday pic 9.
       77 tempmax pic s99.
      * 77 av pic s99v9.
       77 dav pic +99.9.
       77 i pic 9.
       77 line pic x(30) value "-".
       PROCEDURE DIVISION.
       hoofd.
           PERFORM init 
           PERFORM TEST AFTER UNTIL (daynumber = -1)
           PERFORM readday
           PERFORM readtemp
           END-PERFORM
           PERFORM calcav
           PERFORM detmax 
           PERFORM output
           STOP RUN.
           
       init.
           MOVE "monday" TO dayname(1)           
           MOVE "tuesday" TO dayname(2)
           MOVE "wednessday" TO dayname(3)
           MOVE "thursday" TO dayname(4)
           MOVE "friday" TO dayname(5)
           MOVE "saturday" TO dayname(6)
           MOVE "sunday" TO dayname(7).
                      
      * read the daynumber
       readday.
                                                          
           PERFORM TEST AFTER UNTIL (daynumber = -1 OR number)    
             DISPLAY "Give daynumber, -1 to stop"
             ACCEPT daynumber NO BEEP
           END-PERFORM
           
           IF (daynumber = -1)
             THEN perform calcav
           END-IF.
           
      * read the temperature for that day
       readtemp.
           MOVE 1 TO daynumber
           
           DISPLAY "Give temperature for this day"
           ACCEPT temp NO BEEP
           
           COMPUTE sum(daynumber) = sum(daynumber) + temp
           COMPUTE counter(daynumber) = counter(daynumber) + 1
           
           IF temp > max(daynumber)
             THEN MOVE temp TO max(daynumber)
           END-IF.
           
      * calculate the average temperature
       calcav.
           MOVE 1 TO daynumber
           
           PERFORM UNTIL (daynumber > 7)
             COMPUTE av(daynumber) = sum(daynumber) / 
      -       counter(daynumber) 
             ADD 1 TO daynumber
           END-PERFORM.
       
      * determine the maximum temperature for that day 
       detmax.
           MOVE 2 TO daynumber
           
           PERFORM UNTIL (daynumber > 7)
             IF max(daynumber) > max(daynumber - 1)
               THEN MOVE max(daynumber) TO tempmax
                    MOVE dagnaam(daynumber) TO hdag
             END-IF
             COMPUTE daynumber = daynumber + 1
           END-PERFORM.
           
       output.    
           MOVE 1 TO daynumber
           DISPLAY "day       max    average"
           DISPLAY line  
           PERFORM UNTIL (daynumber > 7)
             MOVE av(daynumber) TO dav
             DISPLAY dayname(daynumber) max(daynumber)    dav 
           END-PERFORM
           
           DISPLAY line
           DISPLAY "The warmest day was" hdag "with" tempmax "degrees".
 
First, you need to tell us what the brand and version of Cobol are you using.



Steve
 
Additionally;

Check out the faq's section of this forum, specifically; faq209-500; "How does a conditional Work? (the level 88 thing)," you have some major problems in this area; both in syntax and usage.

You are using Cobol reserved words "sum" "number" "line" and "output" as data-name(s) or condition-name(s).

Steve
 
After you tell us what compiler you are using, can I suggest that if you are just learning COBOL, that you try to limit your code to ANSI/ISO Standard COBOL?

For example, if you have an inline PERFORM, you *must* code an END-PERFORM - not just a period (full-stop) at the end.

All ANSI/ISO conforming compilers have an option to FLAG (not errors) all extensions, for example, Micro Focus has the
FLAGSTD
and
FLAG(ANSI)

directives.

P.S. Why are you coding "with test after" for all of your PERFORM statements? Do you *REALLY* want to perform the test once - even if the condition is met at the time of the first iteration?

(If you know other languages, do you REALLY want a
"loop until"
rather than a
"loop while"

Bill Klein
 
Hi,

I'm sorry it took so long.
The version of Cobol compiler I'm using version 5.30.00 for DOS 2.00+

Sofie
 
Who is the compiler vendor? What is your o/s?
Here is a version modified to work with my compiler.

BTW Bill--WITH TEST AFTER is correct for the two PERFORM statements in which it is coded. And, I don't see any improperly coded in-line performs.
Code:
 IDENTIFICATION DIVISION.
 PROGRAM-ID. examen.
 DATA DIVISION.
 WORKING-STORAGE SECTION.
 01  temperature.
    03  wday occurs 7.
       05  dayname pic x([COLOR=red]9[/color]).
       05  max     pic s99   value -99.
       05  [COLOR=red]t-[/color]sum   pic s999  value 0.
       05  counter pic 99    value 0.
       05  av      pic s99v9.
 77  daynumber     pic s9.
     88  [COLOR=red]is-[/color]number           value 1 thru 7.
 77 temp           pic s99.
 77 hday           pic 9.
 77 tempmax        pic s99   [COLOR=red]value -99[/color].
*77 av             pic s99v9.
 77 dav            pic +99.9.
 77 i              pic 9.
 77 [COLOR=red]h-[/color]line         pic x(30) value [COLOR=red]ALL[/color] "-".
 PROCEDURE DIVISION.
 hoofd.
     PERFORM init 
     PERFORM TEST AFTER UNTIL (daynumber = -1)
         PERFORM readday
         [COLOR=red]IF is-number[/color]
             PERFORM readtemp
         [COLOR=red]END-IF[/color]
     END-PERFORM
     PERFORM calcav
     PERFORM detmax 
     PERFORM [COLOR=red]do-[/color]output
     STOP RUN.
           
 init.
     MOVE "Monday   " TO dayname(1)           
     MOVE "Tuesday  " TO dayname(2)
     MOVE "Wednesday" TO dayname(3)
     MOVE "Thursday " TO dayname(4)
     MOVE "Friday   " TO dayname(5)
     MOVE "Saturday " TO dayname(6)
     MOVE "Sunday   " TO dayname(7).
                      
* read the daynumber
readday.                                                      PERFORM TEST AFTER UNTIL (daynumber = -1 OR [COLOR=red]is-[/color]number)    
      DISPLAY "Give daynumber, -1 to stop"
      ACCEPT daynumber NO BEEP
  END-PERFORM.
[s]IF (daynumber = -1)
             THEN perform calcav
           END-IF.[/s]

* read the temperature for that day
 readtemp.
      [s]MOVE 1 TO daynumber[/s]         
      DISPLAY "Give temperature for " [COLOR=red]dayname(daynumber)[/color]
      ACCEPT temp NO BEEP
      ADD temp TO [COLOR=red]t-[/color]sum  (daynumber)
      ADD 1    TO counter(daynumber)
      IF temp > max(daynumber)
          MOVE temp TO max(daynumber)
      END-IF.
           
* calculate the average temperature
 calcav.
     MOVE 1 TO daynumber      
     PERFORM UNTIL (daynumber > 7)
         COMPUTE av(daynumber) = t-sum(daynumber) / counter(daynumber) 
         ADD 1 TO daynumber
     END-PERFORM.
       
* determine the maximum temperature for [COLOR=red]any[/color] day 
 detmax.
     MOVE [COLOR=red]1[/color]   TO daynumber
     PERFORM UNTIL (daynumber > 7)
         IF max(daynumber) > max(daynumber - 1)
             MOVE max(daynumber) TO tempmax
             MOVE daynumber TO hday
         END-IF
         ADD 1 TO daynumber
     END-PERFORM.
           
 [COLOR=red]do-[/color]output.    
     MOVE 1 TO daynumber
     DISPLAY "day       max    average"
     DISPLAY [COLOR=red]h-[/color]line  
     PERFORM UNTIL (daynumber > 7)
         MOVE av(daynumber) TO dav
         DISPLAY dayname(daynumber) max(daynumber) dav 
         [COLOR=red]ADD 1 TO daynumber[/color]
     END-PERFORM      
     DISPLAY [COLOR=red]h-[/color]line
     DISPLAY "The warmest day was " [COLOR=red]dayname([/color]hday[COLOR=red])[/color] " with " tempmax " degrees".
 
I don't see any missing END-PERFORM, but I do see

PERFORM readtemp
END-PERFORM

in the initial code - which is non-Standard, i.e. includes END-PERFORM with an out-of-line PERFORM. This may (or may not) have been what I saw earlier.

Bill Klein
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top