Menu

Can't Use LOG, SIN, SQRT functions

Tom Lake
2023-05-25
2023-07-01
  • Tom Lake

    Tom Lake - 2023-05-25

    Is there a trick to using transcendental functions in GNUCOBOL? I get a 'not defined' error for any functions I try. I see the functions in the manual but don't see how to activate them.

     
    • Simon Sobisch

      Simon Sobisch - 2023-05-25

      The standard way is to write the FUNCTION keyword in front of them.

      As an alternative you can use the REPOSITORY paragraph: FUNCTION ALL INTRINSIC.

      ... or go non standard and imply that - see

        cobc --help | grep FUNCTION
      
       
      • Tom Lake

        Tom Lake - 2023-05-25

        Thanks! I was a professional COBOL programmer for many years but I worked in the insurance business and financial sector. We never had much use for SIN, COS, TAN or SQRT!

         
        • Vincent (Bryan) Coen

          On 25/05/2023 12:59, Tom Lake wrote:

          Thanks! I was a professional COBOL programmer for many years but I
          worked in the insurance business and financial sector. We never had
          much use for SIN, COS, TAN or SQRT!

          Use the Programmers Guide (found on SF site at :
          https://gnucobol.sourceforge.io/guides.html ) for a full list of all
          functions and there are a lot of them many of which are applicable to
          programming for business and other commercial applications and yes, I
          use a reasonable amount of them :)

          Very handy.

          Vincent

           
  • Anonymous

    Anonymous - 2023-07-01

    For those like me whose C is abysmal a pure COBOL solution:

           IDENTIFICATION DIVISION.
           PROGRAM-ID. TESTSINE.
           ENVIRONMENT DIVISION.
           CONFIGURATION SECTION.
           SOURCE-COMPUTER. UNIVAC-1100.
           OBJECT-COMPUTER. UNIVAC-1100.
           DATA DIVISION.
           WORKING-STORAGE SECTION.
           01  MY-FUNCTION PIC X(4).
           01  ANGLE-THETA PIC 9(4)V9(6) COMP.
           01  SINE-THETA PIC 9(2)V9(8) COMP.
           01  ACCEPT-SINE PIC V99999.
           01  ACCEPT-ANGLE PIC 99V99.
           PROCEDURE DIVISION.
           SOJ.
               DISPLAY 'ENTER FUNCTION'.
                        ACCEPT MY-FUNCTION.
               IF MY-FUNCTION EQUAL 'END' GO TO EOJ.
               IF MY-FUNCTION EQUAL 'SIN'
                   DISPLAY 'ENTER ANGLE-THETA'
                   ACCEPT ACCEPT-ANGLE MOVE ACCEPT-ANGLE TO ANGLE-THETA.
               IF MY-FUNCTION EQUAL 'ASIN' DISPLAY 'SINE ?'
                   ACCEPT ACCEPT-SINE MOVE ACCEPT-SINE TO SINE-THETA.
               CALL 'SINE' USING MY-FUNCTION ANGLE-THETA SINE-THETA.
               DISPLAY 'ANGLE ' ANGLE-THETA ' SINE ' SINE-THETA.
               GO TO SOJ.
           EOJ.
               STOP RUN.
    

    and

           IDENTIFICATION DIVISION.
           PROGRAM-ID. SINE.
           AUTHOR. JACK TEARLE.
           DATE-WRITTEN. SEPT 1983.
           ENVIRONMENT DIVISION.
           CONFIGURATION SECTION.
           SOURCE-COMPUTER. UNIVAC-1100-60.
           OBJECT-COMPUTER.   UNIVAC-1100-60.
           DATA DIVISION.
           WORKING-STORAGE SECTION.
           01  INPUT-SINE PIC 9V9(9) COMP.
           01  WORK-ANGLE PIC S9(3)V9(7) COMP.
           01  LOW PIC S9(2)V9(8) COMP.
           01  ABS-DIFF PIC 9(2)V9(8) COMP.
           01  HIGH PIC S9(2)V9(8) COMP.
           01  RADIANS PIC 99V9(8) COMP.
           01  PI PIC 9V99999999 COMP VALUE 3.14159265.
           LINKAGE SECTION.
           01  FUNCTION PIC X(4).
           01  ANGLE-THETA PIC 9(4)V9(6) COMP.
           01  SINE-THETA PIC 9(2)V9(8) COMP.
           PROCEDURE DIVISION USING FUNCTION ANGLE-THETA SINE-THETA.
           BEGIN.
               MOVE ANGLE-THETA TO WORK-ANGLE.
               IF FUNCTION EQUAL 'ASIN' MOVE SINE-THETA TO INPUT-SINE
                                                     WORK-ANGLE
                   PERFORM CALC-ARCSINE THRU CALC-ARCSINE-EXIT
                   MOVE WORK-ANGLE TO ANGLE-THETA.
               IF FUNCTION EQUAL 'SIN'
                   MOVE ANGLE-THETA TO WORK-ANGLE
                   PERFORM CALC-SINE.
           EOJ.
               EXIT PROGRAM.
           CALC-SINE.
               IF WORK-ANGLE EQUAL ZERO
                   MOVE ZERO TO SINE-THETA
               ELSE
                    COMPUTE RADIANS = PI / (180 / WORK-ANGLE)
                    COMPUTE SINE-THETA
                      = RADIANS - RADIANS ** 3 / 6 + RADIANS ** 5 / 120
                      - RADIANS ** 7 / 5040 + RADIANS ** 9 / 362880.
           CALC-ARCSINE.
               MOVE 90 TO HIGH.
               MOVE 0 TO LOW.
               MOVE ZERO TO ABS-DIFF.
               MOVE ZERO TO SINE-THETA.
           SPT01.
               SUBTRACT SINE-THETA FROM INPUT-SINE GIVING ABS-DIFF.
               IF ABS-DIFF GREATER THAN .00001
                ADD LOW HIGH GIVING WORK-ANGLE ROUNDED
                   DIVIDE 2 INTO WORK-ANGLE
                   PERFORM CALC-SINE
                   IF SINE-THETA GREATER THAN INPUT-SINE
                       MOVE WORK-ANGLE TO HIGH GO TO SPT01
                   ELSE
                       MOVE WORK-ANGLE TO LOW GO TO SPT01.
           CALC-ARCSINE-EXIT.
               EXIT.
    
     

    Last edit: Simon Sobisch 2023-07-01
    • Simon Sobisch

      Simon Sobisch - 2023-07-01

      FUNCTION SIN () is quite "COBOL", too ;-)

      But thanks for sharing that code. Are the DATE-WRITTEN and SOURCE-COMPUTER for real?

       
  • Jack Tearle

    Jack Tearle - 2023-07-01

    Yes. It even compiles and runs in gnucobol. The only change 'FUNCTION' to 'MY-FUNCTION' (reserved word).
    More depressing than having written it 40 years ago, is that I already had 12 years experience.

     
    👍
    2
    • Simon Sobisch

      Simon Sobisch - 2023-07-01

      Keep the original (with FUNCTION, and compile with -std=cobol85 or with -fnot-reserved=FUNCTION should work, too.

      EDIT: I stand corrected, while both options should work, they don't. That's a bug which will be solved; tried with [r5098] but that showed another bug - somehow FUNCTION is always reserved ?!?

      Workaround: add REPLACE FUNCTION BY FUNC. in the first line.

       

      Related

      Commit: [r5098]


      Last edit: Simon Sobisch 2023-07-01

Anonymous
Anonymous

Add attachments
Cancel