Programming Fundamentals/Conditions/COBOL

From Wikiversity
Jump to navigation Jump to search

conditions.cbl[edit | edit source]

*> This program asks the user for a Fahrenheit temperature, 
*> converts the given temperature to Celsius,
*> and displays the results.
*>
*> References:
*>     https://www.mathsisfun.com/temperature-conversion.html
*>     https://www.tutorialspoint.com/cobol/index.htm
*>     https://open-cobol.sourceforge.io/doc/gnucobol.html

IDENTIFICATION DIVISION.
PROGRAM-ID. CONDITIONS.

DATA DIVISION.
WORKING-STORAGE SECTION.
01 CHOICE       PIC X.
01 TEMP-IN      PIC 999V99.
01 TEMP-OUT     PIC ZZ9.99.
01 LABEL-IN     PIC X(10).
01 LABEL-OUT    PIC X(10).

PROCEDURE DIVISION.

MAIN.
    *> MAIN could either be an IF-ELSE structure or an EVALUATE structure

    DISPLAY "Enter F to convert to Fahrenheit or C to convert to Celsius:".
    ACCEPT CHOICE

    *> IF-ELSE approach
    IF CHOICE = "C" OR CHOICE = "c" THEN
        MOVE "Fahrenheit" TO LABEL-IN
        MOVE "Celsius" TO LABEL-OUT
        PERFORM GET-TEMPERATURE
        PERFORM COMPUTE-CELSIUS
        PERFORM DISPLAY-RESULT
    ELSE 
        IF CHOICE = "F" OR CHOICE = "f" THEN
            MOVE "Celsius" TO LABEL-IN
            MOVE "Fahrenheit" TO LABEL-OUT
            PERFORM GET-TEMPERATURE
            PERFORM COMPUTE-FAHRENHEIT
            PERFORM DISPLAY-RESULT
        ELSE
            DISPLAY "You must enter C to convert to Celsius or F to convert to Fahrenheit!"
        END-IF
    END-IF.
    
    *> EVALUATE approach
    EVALUATE TRUE
        WHEN CHOICE = "C" OR CHOICE = "c"
            MOVE "Fahrenheit" TO LABEL-IN
            MOVE "Celsius" TO LABEL-OUT
            PERFORM GET-TEMPERATURE
            PERFORM COMPUTE-CELSIUS
            PERFORM DISPLAY-RESULT
        WHEN CHOICE = "F" OR CHOICE = "f"
            MOVE "Celsius" TO LABEL-IN
            MOVE "Fahrenheit" TO LABEL-OUT
            PERFORM GET-TEMPERATURE
            PERFORM COMPUTE-FAHRENHEIT
            PERFORM DISPLAY-RESULT
        WHEN OTHER
            DISPLAY "You must enter C to convert to Celsius or F to convert to Fahrenheit!"
    END-EVALUATE.

    STOP RUN.

GET-TEMPERATURE.
    DISPLAY "Enter " LABEL-IN " temperature:".
    ACCEPT TEMP-IN.

COMPUTE-CELSIUS.
    COMPUTE TEMP-OUT = (TEMP-IN - 32) * 5 / 9.

COMPUTE-FAHRENHEIT.
    COMPUTE TEMP-OUT = TEMP-IN * 9 / 5 + 32.

DISPLAY-RESULT.
    DISPLAY TEMP-IN "° " LABEL-IN " is " TEMP-OUT "° " LABEL-OUT.

Try It[edit | edit source]

Copy and paste the code above into one of the following free online development environments or use your own COBOL compiler / interpreter / IDE.

See Also[edit | edit source]