-3

I am trying to run the sub routine in geany, bur it keeps me giving the following warning

NPJ(I,J) = DBLE(((2)/((X(I+1))-(X(I-1))))*DBLE(-((1)/(X(I+1)-X(I)))-((1)/(X(I)-
X(I-1)))))+  & 

             1
Warning: Possible change of value in conversion from REAL(8) to INTEGER(4) at (1)

the code follows by

C(I,J) = -(RE(I,J))/NPJ(I,J)

on the next line.

Everytime I run the program it gives that I am getting divisions by zero.

The code is here:

!   PROJETO 1 - MÉTODOS EXPERIMENTAIS EM HIDRODINÂMICA
!******************************************
!                                                                                  *
!         PROGRAMA PRINCIPAL                                   *
!                                                                                  *
!******************************************

    IMPLICIT DOUBLE PRECISION (A-H,O-Z)
    Parameter (NX = 100, NY = 100)

!   DECLARAÇÃO DE VARIÁVEIS
    COMMON/GRID/X(NX),Y(NY)
    COMMON/RESI/RE(NX,NY)
    COMMON/PTN/ POT(NX,NY)    
    CHARACTER*30 BOBO

!   DEFINIÇÃO DOS ARQUIVOS DE ENTRADA E SAÍDA

    OPEN(3,FILE = 'placa.dat')
    OPEN(4,FILE = 'output.dat')

!   ENTRADA DE DADOS

      READ(3,*) BOBO,IMAX
      WRITE(*,'(A30,I10)')BOBO,IMAX

      READ(3,*) BOBO,JMAX
      WRITE(*,'(A30,I10)')BOBO,JMAX

      READ(3,*) BOBO,t
      WRITE(*,'(A30,F10.3)')BOBO,t

      READ(3,*) BOBO,NMAX
      WRITE(*,'(A30,I10)')BOBO,NMAX

      READ(3,*) BOBO,UA
      WRITE(*,'(A30,D10.3)')BOBO,UA

      READ(3,*) BOBO,UB
      WRITE(*,'(A30,D10.3)')BOBO,UB

      READ(3,*) BOBO,UC
      WRITE(*,'(A30,D10.3)')BOBO,UC

      READ(3,*) BOBO,UD
      WRITE(*,'(A30,D10.3)')BOBO,UD

      READ(3,*) BOBO,UP
      WRITE(*,'(A30,D10.3)')BOBO,UP

      READ(3,*) BOBO,PREC
      WRITE(*,'(A30,D10.3)')BOBO,PREC

      READ(3,*) BOBO,NPR
      WRITE(*,'(A30,I10)')BOBO,NPR

      READ(3,*) BOBO,ITE
      WRITE(*,'(A30,I10)')BOBO,ITE

      READ(3,*) BOBO,ILE
      WRITE(*,'(A30,I10)')BOBO,ILE

      READ(3,*) BOBO,XSF
      WRITE(*,'(A30,F10.3)')BOBO,XSF

      READ(3,*) BOBO,YSF
      WRITE(*,'(A30,F10.3)')BOBO,YSF

!$$$$$$ 
!$$$$$$       WRITE(*,*)"Os dados de entrada estao corretos?"
!$$$$$$       WRITE(*,*)"1--------SIM"
!$$$$$$       WRITE(*,*)"2--------NAO"
!$$$$$$       READ(*,*)INF
!$$$$$$       IF(INF.EQ.2) STOP

!     GERAÇÃO DA MALHA COMPUTACIONAL      

      CALL MALHA(IMAX,JMAX,DX,ITE,ILE,XSF,YSF,DY)

! !     CONDIÇÃO INICIAL

      CALL INICIAL(IMAX,JMAX,UP)


!!!     INÍCIO DAS ITERAÇÕES

     CALL SOLVER(IMAX,JMAX,NMAX,PREC,N,NPR,DY,UA,UB,UD,ILE,ITE,t)

!!     FIM DA EXECUÇÃO

      STOP
      END     

!******************************************
!                                                                                   *
!           SUBROTINA MALHA                                     *
!                                                                                   *
!******************************************      

    SUBROUTINE MALHA(IMAX,JMAX,DX,ITE,ILE,XSF,YSF,DY)
    IMPLICIT DOUBLE PRECISION (A-H,O-Z)
    PARAMETER (NX=100,NY=100)
    COMMON/GRID/ X(NX),Y(NY)

    DX=1.0D0/DBLE(ITE-ILE)


    DO I=ILE,ITE
        X(I)=DX*DBLE(I-ILE)
    END DO

    DO I=ITE,IMAX
        X(I)=X(I-1)+((X(I-1)-X(I-2))*XSF)     
    END DO

    DO I=ILE-1,1,-1
        X(I)=X(I+1)+((X(I+1)-X(I+2))*XSF)     
    END DO

      Y(1) = (-DX)/2.0D0
      Y(2) = DX/2.0D0
      DY = Y(2)-Y(1)
    DO J=3, JMAX
        Y(J)=Y(J-1)+((Y(J-1)-Y(J-2))*YSF)
    END DO  

    RETURN
    END

 !******************************************
!                                                                                                       *
!           SUBROTINA INICIAL                                                   *
!                                                                                                       *
!******************************************

      SUBROUTINE INICIAL(IMAX,JMAX,UP)
      IMPLICIT DOUBLE PRECISION (A-H,O-Z)
      PARAMETER (NX=100,NY=100)
      COMMON/PTN/ POT(NX,NY)
      COMMON/GRID/ X(NX),Y(NY)

      UP = 1.0D0
      DO J=1,JMAX
      DO I = 1,IMAX
        POT(I,J)=UP*X(I)

      END DO
      END DO

      RETURN
      END   

!******************************************
!                                                                                                       *
!           SUBROTINA CONTORNO                                          *
!                                                                                                       *
!******************************************

      SUBROUTINE CONTORNO(IMAX,JMAX,UA,UB,UD,ILE,ITE,DY,t)
      IMPLICIT DOUBLE PRECISION (A-H,O-Z)
      PARAMETER (NX=100, NY=100)
      COMMON/GRID/ X(NX),Y(NY)
      COMMON/PTN/ POT(NX,NY)

! Entrada e Saída
      DO J=1,JMAX
        POT(1,J)=UA*X(1)
        POT(IMAX,J)=UB*X(IMAX)
      END DO

! Fronteira Superior 
      DO I=1, IMAX
        POT(I,JMAX)=UD*X(I)
      END DO

!Simetria     
      DO I=1, IMAX
      POT(I,1) = POT(I,2) 
      END DO

! Sobre o Corpo
      DO I=ILE,ITE
      POT(I,1) = POT(I,2) - 2.0D0*DY*UA*t*(1-(2.0D0*X(I)))   
      END DO

      RETURN
      END


!******************************************
!                                                               *
!           SUBROTINA RESIDUO                             *
!                                                               *
!******************************************

      SUBROUTINE RESIDUO(IMAX,JMAX,TESTE)
      IMPLICIT DOUBLE PRECISION (A-H,O-Z)
      PARAMETER (NX=100, NY=100)
      COMMON/RESI/ RE(NX,NY)
      COMMON/GRID/ X(NX),Y(NY)
      COMMON/PTN/ POT(NX,NY)


!     CALCULO DO RESIDUO
      DO J=2,JMAX-1
      DO I=2,IMAX-1 
      RE(I,J) = ((2.0D0/((X(I+1))-(X(I-1))))*(((POT(I+1,J)-POT(I,J))/(X(I+1)-X(I)))-((POT(I,J)-POT(I-1,J))/(X(I)-X(I-1)))))+ &
                &((2.0D0/((Y(J+1))-(Y(J-1))))*(((POT(I,J+1)-POT(I,J))/(Y(J+1)-Y(J)))-((POT(I,J)-POT(I,J-1))/(Y(J)-Y(J-1)))))

      END DO
      END DO

!     CALCULO DO RESIDUO MAXIMO

      TESTE=0.0D0

      DO J=2,JMAX-1
      DO I=2,IMAX-1
      IF(DABS(RE(I,J)).GT.TESTE) THEN
        TESTE=DABS(RE(I,J))
      END IF
      END DO
      END DO

      RETURN
      END      

!******************************************
!                                                                                                       *
!           SUBROTINA SOLVER                                                    *
!                                                                                                       *
!******************************************

      SUBROUTINE SOLVER(IMAX,JMAX,NMAX,PREC,N,NPR,DY,UA,UB,UD,ILE,ITE,t)
      IMPLICIT DOUBLE PRECISION (A-H,O-Z)
      PARAMETER (NX=100,NY=100)
      COMMON/GRID/ X(NX),Y(NY)
      COMMON/RESI/ RE(NX,NY)
      COMMON/NPJACO/ NPJ(NX,NY)
      COMMON/CORREC/ C(NX,NY)
      COMMON/PTN/ POT(NX,NY)

      TESTE=100.0D0
      N=1
      IMP=NPR-1
      OPEN(10,FILE='remax.dat')

!     INICIO DAS ITERAÇÕES
      CALL CONTORNO(IMAX,JMAX,UA,UB,UD,ILE,ITE,DY,t)
      DO WHILE((N.NE.(NMAX+1)).AND.(TESTE.GT.PREC))



      CALL RESIDUO(IMAX,JMAX,TESTE)

      WRITE(*,*) N,TESTE
      WRITE(10,*) N,TESTE

      DO J=2,JMAX-1
      DO I=2,IMAX-1
        NPJ(I,J) = (((2.0D0)/((X(I+1))-(X(I-1))))*(-((1.0D0)/(X(I+1)-X(I)))-((1.0D0)/(X(I)-X(I-1)))))+  &
            & (((2.0D0)/((Y(J+1))-(Y(J-1))))*(-((1.0D0)/(Y(J+1)-Y(J)))-((1.0D0)/(Y(J)-Y(J-1)))))

        C(I,J) = -(RE(I,J))/NPJ(I,J)

        POT(I,J) = POT(I,J)+C(I,J)   
      END DO
      END DO

      N=N+1
      IMP=IMP+1

!==========================================================================================================
!     SAÍDA DE RESULTADOS

      IF(IMP.EQ.NPR) THEN

      WRITE(4,10) IMAX,JMAX
10  FORMAT('TITLE = " Malha Cartesiana "',/,&
     &       'VARIABLES = X, Y, POT, NPJ, RE',/,&
     &       'ZONE T ="Zone-one", I=',I5,'J=',I5,',F=POINT')   

      DO J=1,JMAX
      DO I=1,IMAX
      WRITE(4,*) 'X',I,':', X(I),Y(J), POT(I,J), NPJ(I,J), RE(I,J)
      END DO
      END DO

      IMP=0
      END IF
!
      END DO

!     FIM DAS ITERAÇÕES

      RETURN 
      END
Leonardo Guerreiro
  • 901
  • 1
  • 9
  • 18
  • 1
    If you want to fix your errors, show us more details. The line and the warning is not enough. Please read [ask] and [mcve]. Do not use pictures and screenshots, paste text. – Vladimir F Героям слава Jul 28 '17 at 15:26
  • The warning you show just says that you are assigning the result of the computation to `NPJ(I,J)` which is likely integer. Nothing less and nothing more. It depends what do you do with `NPJ(I,J)` later, it may be related to the division by zero or it might not be. – Vladimir F Героям слава Jul 28 '17 at 15:28
  • Please do not in the future post screenshots and links to some hosting where the code is saved. Paste the code right here into the question. 1. The question should serve for others int the future, even if the code is deleted from the hosting. 2. Many people (including me) do not want to click on suspicious links to extenal sites and download unkown files. If the file is too long, read [mcve] to find how to make it shorter. Notice you already aquired quite a few downvotes (and I didn't vote eventhough so it may be even more). These can lead to an automatic ban on this site surprisingly quickly. – Vladimir F Героям слава Jul 28 '17 at 21:18
  • I have pasted the code there for you, but please, put it there in yourself in the future and make it shorter. Much shorter. – Vladimir F Героям слава Jul 28 '17 at 21:19

1 Answers1

0

You are not declaring variables in your code, but counting on implicit type. Hence NPJ is an integer array. This is a bad habit. Always declare types, and put IMPLICIT NONE in each program unit. It may require more coding, but it's worth it.

In the assignment to NPJ(I,J), if the right-hand side is small, it will be truncated to zero [1]. Since this line is followed by C(I,J) = -(RE(I,J))/NPJ(I,J), you then get a division by zero.

In your case, NPJ should probably be declared DOUBLE PRECISION. But I didn't investigate much what it's supposed to do anyway.


[1] More precisely, the double precision value (call it A) is converted like if there were INT(A,K) in your code, where K is the integer kind of NPJ (should be default integer here). See section 7.2.1.3 #8 of the Fortran 2008 standard. You will find in section 13.7.81 #5 that INT(A) is zero when |A|<1.

cub
  • 36
  • 2
  • The deleted screenshot was too small to identify if there is implicit typing in place or if it is intentionally declared integer. But you are likely to be right. – Vladimir F Героям слава Jul 28 '17 at 16:08
  • @VladimirF There is a file PROJETO-1.f95 at the [link](https://drive.google.com/drive/folders/0B783lM2aZnWSWjlqN1hlNEpaVFU) given in Leonardo's answer (which shouldn't be an answer, of course you are right). There are `IMPLICIT DOUBLE PRECISION (A-H,O-Z)` in every subroutine. In the SOLVER subroutine, there is a COMMON declaration of NPJ, without any other type information, so default integer. Just after the assignment, there is `C(I,J) = -(RE(I,J))/NPJ(I,J)`, hence division by zero. – cub Jul 28 '17 at 16:19
  • Alright then. I didn't notice the question is not deleted yet (it will be soon). I never click on links to similar services even when the link is put into the question. – Vladimir F Героям слава Jul 28 '17 at 16:23