Code resulting in infinity value

Hello, everyone.

Please, could somebody help-me with the code below? It is resulting in infinity value.

            PROGRAM MR
!============================================================
!DECLARACAO DAS VARIAVEIS
!============================================================
            IMPLICIT NONE
            REAL, EXTERNAL::F
            INTEGER, PARAMETER :: N=6, NPC=4
            INTEGER I, J
            REAL :: X(0:N),Y(0:N),A(0:N-1),B(0:N-1)

            OPEN(UNIT=20, FILE="FUNCA.txt", STATUS="UNKNOWN")
!============================================================
!DADOS DA FUNCAO INTERPOLADA
!============================================================
            PRINT*, "DADOS DA FUNCAO"
            DO I=0, N
                X=X(I)+1
                Y(I)=F(X)
                WRITE(20,*)X(I),Y(I)
                WRITE(*,*)I,X(I),Y(I)
            END DO
!============================================================
!COEFICIENTES DAS FUNCOES INTERPOLADAS
!============================================================
            PRINT*, "COEFICIENTE DAS FUNCOES"
            DO I=0, N-1
                A(I)=(Y(I+1)-Y(I))/(X(I+1)-X(I))
                B(I)=(Y(I)*X(I+1)-(I)*Y(I+1))/(X(I+1)-X(I))
            WRITE (*,*)I,A(I),B(I)
            END DO

            END PROGRAM MR
!============================================================
!FUNCAO
!============================================================
            REAL FUNCTION F(X)
            IMPLICIT NONE
            REAL::x
            F = SIN(X/2)
            END

The results is:

Blockquote
DADOS DA FUNCAO
0 1.00000000 0.479425550
1 2.00000000 0.841470957
2 3.00000000 0.997494996
3 4.00000000 0.909297407
4 5.00000000 0.598472118
5 6.00000000 0.141120002
6 7.00000000 -0.350783229
COEFICIENTE DAS FUNCOES
0 Infinity Infinity
1 Infinity Infinity
2 -Infinity Infinity
3 -Infinity Infinity
4 -Infinity Infinity
5 -Infinity Infinity

Process returned 0 (0x0) execution time : 0.035 s
Press any key to continue.

Thank you!!

The code

            DO I=0, N
                X=X(I)+1
                Y(I)=F(X)
                WRITE(20,*)X(I),Y(I)
                WRITE(*,*)I,X(I),Y(I)
            END DO

does not look right to me, because I don’t see where X is previously set. Do you realize that

X=X(I)+1

is setting all values of array X to X(I)+1?

1 Like
            DO I=0, N
                X=X(I)+1
                Y(I)=F(X)
                WRITE(20,*)X(I),Y(I)
                WRITE(*,*)I,X(I),Y(I)
            END DO

gfortran 12.2.0 gives a rank mismatch in argument x, but ifort 2021.7.0 20220726 compiles without error.

Hello @Beliavsky , thank for your answer.

I just would like to make a list with numbers from 0-N and in the X array and then use this values in the next “DO” for the functions.

Do you know how could I fix that?

@Ali , Im beginner and Im using Code Blocks with Gfortran as compiler

I suggest putting functions in modules, as shown in the code below, which may do what you want.

            module f_mod
            implicit none
            contains
            REAL FUNCTION F(X)
            IMPLICIT NONE
            REAL::x
            F = SIN(X/2)
            END
            end module f_mod
!
            PROGRAM MR
!============================================================
!DECLARACAO DAS VARIAVEIS
!============================================================
            use f_mod, only: f
            IMPLICIT NONE
            INTEGER, PARAMETER :: N=6, NPC=4
            INTEGER I
            REAL :: X(0:N),Y(0:N),A(0:N-1),B(0:N-1)

            OPEN(UNIT=20, FILE="FUNCA.txt", STATUS="UNKNOWN")
!============================================================
!DADOS DA FUNCAO INTERPOLADA
!============================================================
            PRINT*, "DADOS DA FUNCAO"
            DO I=0, N
                X(I) = REAL(I)
                Y(I) = F(X(I))
                WRITE(20,*)X(I),Y(I)
                WRITE(*,*)I,X(I),Y(I)
            END DO
!============================================================
!COEFICIENTES DAS FUNCOES INTERPOLADAS
!============================================================
            PRINT*, "COEFICIENTE DAS FUNCOES"
            DO I=0, N-1
                A(I)=(Y(I+1)-Y(I))/(X(I+1)-X(I))
                B(I)=(Y(I)*X(I+1)-(I)*Y(I+1))/(X(I+1)-X(I))
            WRITE (*,*)I,A(I),B(I)
            END DO

            END PROGRAM MR
2 Likes

First, welcome to the forum.

Now big NOTE, you do not initialise X in any way, and so the first assignment X = X(I) + 1, is techinically undefined behavior and not standards conforming Fortran. gfortran happens to have initialised it to zero for you, but this is not necessarily the case for all compilers or all modes of operation. I recommend the compiler flags -finit-real=snan -ffpe-trap=invalid,zero,overflow,underflow,denormal to catch these kinds of mistakes.

Now the explanation, In the first loop, you are assigning to all elements of the array X, and so once that loop has completed, all values in X are 7.0. Then, in the second loop, the subtraction in the denominator results in 0.0, and the division produces infinity. The flags I mentioned prior would catch this error as well. I suspect you meant something like the following:

PROGRAM MR
!============================================================
!DECLARACAO DAS VARIAVEIS
!============================================================
            IMPLICIT NONE
            REAL, EXTERNAL::F
            INTEGER, PARAMETER :: N=6, NPC=4
            INTEGER I, J
            REAL :: X(0:N),Y(0:N),A(0:N-1),B(0:N-1)

            OPEN(UNIT=20, FILE="FUNCA.txt", STATUS="UNKNOWN")
!============================================================
!DADOS DA FUNCAO INTERPOLADA
!============================================================
            PRINT*, "DADOS DA FUNCAO"
            X(0) = 0.0
            Y(0) = F(X(0))
            DO I=1, N
                X(I)=X(I-1)+1.0
                Y(I)=F(X(I))
                WRITE(20,*)X(I),Y(I)
                WRITE(*,*)I,X(I),Y(I)
            END DO
!============================================================
!COEFICIENTES DAS FUNCOES INTERPOLADAS
!============================================================
            PRINT*, "COEFICIENTE DAS FUNCOES"
            DO I=0, N-1
                A(I)=(Y(I+1)-Y(I))/(X(I+1)-X(I))
                B(I)=(Y(I)*X(I+1)-(I)*Y(I+1))/(X(I+1)-X(I))
            WRITE (*,*)I,A(I),B(I)
            END DO

            END PROGRAM MR
!============================================================
!FUNCAO
!============================================================
            REAL FUNCTION F(X)
            IMPLICIT NONE
            REAL::x
            F = SIN(X/2)
            END
2 Likes

Side question: in this example you write implicit none both in the module and again in the function contained in the module. I am wondering whether this is redundant or not. In other words, if you write implicit none at the start of a module, does it automatically apply to all functions and subroutines contained in the module?

Yes, it does, so the implicit none in the function was redundant.

1 Like