2

Right now I am dealing with Fortran codes of the man who worked on the project before me. The code is relatively huge so I would not provide it here. In a lot of places in this codes there are division of double precision value over integer. I.e.:

double precision :: a,c
integer :: b
a = 1.0d0
b = 3
c = a/b

This sometimes leads to a mistakes much worse than a regular floating point number mistake. I will copypaste one of such mistakes for you: 3.00000032899483. For his purposes this was OK, but for me this mistake is awful. It seems like fortran is dividing real number over integer and then enlarge number to double precision, adding some random stuff. It can be treated of course if I will write:

c = a/(real(b,8))

So, I can do it, but it will take very long time to search through all his codes. That's why, I tried to overload (/) operator in the next way:

MODULE divisionoverload
!-----------------------------------------------------
   INTERFACE OPERATOR (/)
      MODULE PROCEDURE real_divoverinteger
   END INTERFACE OPERATOR ( / )
CONTAINS
!-----------------------------------------------------

DOUBLE PRECISION FUNCTION real_divoverinteger(a,b)
   IMPLICIT NONE
   DOUBLE PRECISION, INTENT (IN) :: a 
   INTEGER, INTENT(IN) :: b 

   real_divoverinteger = a/real(b,8)
END FUNCTION real_divoverinteger

END MODULE divisionoverload

But the mistake gfortran4.8 gives me clearly indicates that this conflicts with intrinsic division operator:

 MODULE PROCEDURE real_divoverinteger
                                          1
Error: Operator interface at (1) conflicts with intrinsic interface

So what can I do to solve this problem without manually handling all the divisions by integer?

Code which generates such numbers with printing format:

 hx = (gridx(Nx1+1)-gridx(Nx1))/modx)
 do i = 2,lenx
    sub%subgridx(i)=sub%subgridx(i-1) + hx
 end do
 !*WHERE*
 !hx,gridx[1d array], sub%subgridx[1d array] - double precision
 !modx, lenx - integer

code for printing

subroutine PrintGrid(grid,N)
    integer, intent (in) :: N       
    double precision, dimension(N), intent (in) :: grid
    integer :: i
    print"(15(f20.14))", (grid(i), i=1,N)
        print*, ""
end subroutine PrintGrid

Solution: I apologize for this question. I should read code more careful. I found a mistake. The reproduction for the problem you get get in the next way:

program main
   double precision :: a
   a = 1.0/3
   print*, a
end program main

So basically, he was performing real/integer division and assigned this value to real*8. I changed everything with codes like this:

 program main
   double precision :: a
   a = 1.0d0/3
   print*, a
end program main

And it worked! Thank you very much for help, without your answers I would be dealing with this problem much more.

Gogrik
  • 48
  • 1
  • 1
  • 6
  • I guess that "mistake" should be read as "rounding error" or some similar meaning here, right? And when you say that this error is for example "3.00000032899483", where does this value come from? How did you get it? How did you print it? – Gilles Feb 24 '16 at 09:58
  • I added exact codes which generates such a mistakes. And no, under mistakes I don't mean rounding error. If I write the integer as real(b,8) I see numbers like 3.0000000000000001, this can be considered as rounding mistake. If you compare this number to 3 with intrinsic fortran operator "==" you will get .true. And 3.00000032899483 == 3.d0 = .false. – Gogrik Feb 24 '16 at 10:09
  • Gilles answer is correct. Any fortran compiler that doesn't behave this way is broken. If I turn the code snippet above into a complete program and write out the value of c I get 0.33333333333333331 when compiled with gfortran 4.8. Could you show a complete code that shows your problem and prints out the value 3.00000032899483, please? – Ian Bush Feb 24 '16 at 10:36
  • The exact code which is "healed" after adding real(8,modx) I provided with the update of my post. Gilles answer is right, I wrote same routines and get a right answer. Nevertheless, something is going wrong when I am running his program. I will try to extract the problematic code and I will put it to my post. – Gogrik Feb 24 '16 at 10:54

2 Answers2

8

I believe the initial assertion of your question, which is (if I understand you well) that dividing a real by an integer leads to lesser precision than dividing by a real, is wrong. Fortran promotes the weakest type of the two operands of an operation (if needed) to the strongest type, prior to compute the operation. Therefore, doing the promotion yourself is unnecessary.

See the following code for example:

program promotion
    implicit none
    integer, parameter :: dp = kind( 1.d0 )
    integer :: i
    real( kind = dp ) :: a

    i = 3
    a = 1
    print *, "division by a real:", a/real(i,dp), "division by an integer:", a/i
    print *, "are they equal?", a/real(i,dp) == a/i
end program promotion

The actual printing of the results may differ from one compiler to the next, but the final test will always evaluate to .true.

~/tmp$ gfortran promotion.f90
~/tmp$ ./a.out 
 division by a real:  0.33333333333333331      division by an integer:  0.33333333333333331     
 are they equal? T
Gilles
  • 9,269
  • 4
  • 34
  • 53
4

as noted your title claim is incorrect, integer division is automatically upcast and is fine.

Your first example, however does have a problem:

program main
   double precision :: a
   a = 1.0/3
   print*, a
end program main

here we have a single precision 1.. The 3 gets promoted to single precision, so you have a single precision approximation to 1/3 assigned to your double precision a. The fix is to make the 1.0 1.d0.

Monkeying around overloading operators feels like a bad idea to me. If there is really to much code to manually fix see if your compiler has an option to change the default literal type to double.

agentp
  • 6,849
  • 2
  • 19
  • 37
  • You definitely right, I found this mistake. That's why I marked it as a SOLUTION. I thought the guy before me was smart enough to use 1.0d0, but instead he used 1.0. Anyway, thanks) – Gogrik Feb 24 '16 at 13:13
  • The proper approach is to post your "solution" as an answer. Even accept it yourself if you think your answer is the best one. As stands your question is very confusing. – agentp Feb 24 '16 at 14:39