CPP de la commande CW (calcul en fenetre)

BoTTom |
       IDENTIFICATION DIVISION.
       PROGRAM-ID. CWCPP.
       ENVIRONMENT DIVISION.
       INPUT-OUTPUT SECTION.
       FILE-CONTROL.  SELECT ECRAN ASSIGN TO WORKSTATION-CWD-SI
                      ORGANIZATION TRANSACTION.
       DATA DIVISION.
       FILE SECTION.
       FD ECRAN.
       01 BUFFER.
          02 f1 pic s9(10)v99.
          02 op pic x.
          02 f2 pic s9(10)v99.
          02 zr pic s9(12)v999.
       WORKING-STORAGE SECTION.
       01 indtab.
          02 ind pic 1 occurs 99 indicator 01.
       77 ef pic 1 value b"1".
       77 F3 LIKE F2.
       PROCEDURE DIVISION.
           open i-o ecran.
           move zero to f1 f2 zr.
           perform affichage.
           move ef to ind(40)
           perform until ind(03) = ef
             evaluate op
             when "+" if ind(08) = ef
                         compute zr = (f1 + ((f1 * f2) / 100))
                         on size error move ef to ind(31)
                         end-compute
                      else
                         compute zr = (f1 + f2)
                         on size error move ef to ind(31)
                         end-compute
                      end-if
             when "-" if ind(08) = ef
                         compute zr = (f1 - ((f1 * f2) / 100))
                         on size error move ef to ind(31)
                         end-compute
                      else
                         compute zr = (f1 - f2)
                         on size error move ef to ind(31)
                         end-compute
                      end-if


|
             when "*" if ind(08) = ef
                         move ef to ind(30)
                      else
                         compute zr = (f1 * f2)
                         on size error move ef to ind(31)
                         end-compute
                      end-if
             when "/" if ind(08) = ef
                         move ef to ind(30)
                      else
                         compute zr = (f1 / f2)
                         on size error move ef to ind(31)
                         end-compute
                      end-if
             when "P" if ind(08) = ef
                         move ef to ind(30)
                      else
                         move f1 to zr
                         move zero to f3
                         perform varying f3 from 1 by 1
                          until f3 = f2  or ind(31) = ef
                             compute zr = (zr * f1)
                             on size error move ef to ind(31)
                             end-compute
                         end-perform
                      end-if
             end-evaluate
           perform affichage
           end-perform.
           close ecran stop run.
       affichage.
             write buffer format "FMT" indic indtab
             read  ecran  format "FMT" indic indtab.




©AF400