How to cast a real as a specific KIND? - casting

I have multiple kinds I am using in Fortran and would like to add a real valued number where the real number is cast as that kind.
For example, something like:
program illsum
implicit none
#if defined(USE_SINGLE)
integer, parameter :: rkind = selected_real_kind(6,37)
#elif defined(USE_DOUBLE)
integer, parameter :: rkind = selected_real_kind(15,307)
#elif defined(USE_QUAD)
integer, parameter :: rkind = selected_real_kind(33, 4931)
#endif
integer :: Nmax = 100
integer :: i
real(kind = rkind) :: mysum = 0.0
do i = 1,Nmax
mysum = mysum + kind(rkind, 1.0)/kind(rkind, i)
enddo
end program illsum
So I want to make sure that 1.0 and the real valued expression of i are expressed as the proper kind that I have chosen before performing the division and addition.
How can I cast 1.0 as rkind?

To convert a numeric value to a real value then there is the real intrinsic function. Further, this takes a second argument which determines the kind value of the result. So, for your named constant rkind
real(i, rkind) ! Returns a real valued i of kind rkind
real(1.0, rkind) ! Returns a real valued 1 of kind rkind
which I think is what you are meaning with kind(rkind, 1.0). kind itself, however, is an intrinsic which returns the kind value of a numeric object.
However, there are other things to note.
First, the literal constant 1._rkind (note the . in there, could be clearer with 1.0_rkind) which is of kind rkind and value approximating 1.
There's no comparable expression i_rkind, though, so the conversion above would be necessary for a real result of kind rkind with value approximating i.
That said, for you example there is no need to do such casting of the integer value. Under the rules of Fortran the expression 1._rkind/i involves that implicit conversion of i and is equivalent to 1._rkind/real(i,rkind) (and real(1.0, rkind)/real(i,rkind)).

Related

How to resolve the issue with signed zero?

I came to know about 'signed zeroes' only now as I am trying to deal with complex numbers. Here is the problem:
PROGRAM sZ
IMPLICIT NONE
REAL(KIND(0.d0)),PARAMETER :: r=0.2
COMPLEX(KIND(0.d0)) :: c0
c0=(0.0,0.5); print*,sqrt(c0**2-r)
c0=(-0.0,0.5); print*,sqrt(c0**2-r)
END PROGRAM sZ
The sign of the imaginary part changes.
(0.0000000000000000,0.67082039547127081)
(0.0000000000000000,-0.67082039547127081)
Any instructions/suggestions to resolve this issue are very much welcome.
The values you see follow from the intermediate step and the specification of the sqrt intrinsic.
The final result depends on the value of the argument to sqrt: as the result has real part the sign of the result's imaginary part is that of the sign of the argument's imaginary part.
What are the signs of the imaginary parts of the two arguments? The imaginary parts of (0.,0.5) and (-0.,0.5) squared are positive in the first case and negative in the second (with the expected implementation of signed zero). Subtracting a real entity does not affect the sign of the imaginary part of the object which becomes the argument to sqrt.
At one level, you are getting the correct result so the only thing to resolve is your expectation of getting the same result. However, consider
implicit none
complex :: z1=(-1.,0.), z2=(-1.,-0.)
print*, z1==z2, SQRT(z1)==SQRT(z2)
end program
It is easy to see why this is confusing even if correct. If we don't want this to happen, we can force any zero imaginary part to be of one particular sign (say, non-negative):
! Force imaginary part away from -0.
if (z%Im==0.) z%Im = 0.
(A comment for this is very necessary.)
We can access and set the imaginary part of a complex variable using the z%Im designator, but this is not possible for general expressions. You may want to create a function for more general use:
implicit none
complex :: z1=(-1.,0.), z2=(-1.,-0.)
print*, z1==z2, SQRT(z1)==SQRT(z2)
print*, z1==z2, SQRT(design_0imag(z1))==SQRT(design_0imag(z2))
contains
pure complex function design_0imag(z) result(zp)
complex, intent(in) :: z
zp = z
if (zp%Im==0.) zp%Im = 0.
end function design_0imag
end program
As shown by other answers, there are several ways to implement logic replacing -0 with 0 (leaving other values unchanged). Remember that you experience this only when the result is purely imaginary.
you could do something like this, so a signed (negative) zero is just caught and replaced with zero.
PROGRAM sZ
IMPLICIT NONE
REAL(KIND(0.d0)),PARAMETER :: r=0.2
COMPLEX(KIND(0.d0)) :: c0
REAL(KIND(0.d0)),PARAMETER :: i = -0.0
REAL(KIND(0.d0)),PARAMETER :: j = 0.5
REAL(KIND(0.d0)),PARAMETER :: zero = 0.0
if (i .EQ. 0) then
c0 = (zero, j); print*,sqrt(c0**2-r)
else
c0=(i, j); print*,sqrt(c0**2-r)
end if
END PROGRAM sZ
I have devised one little hack to remove this signed zeros.
PROGRAM sZ
IMPLICIT NONE
REAL(KIND(0.d0)),PARAMETER :: r=0.2
COMPLEX(KIND(0.d0)) :: c0,zero
zero=(0.0,0.0)
c0=(0.0,0.5); c0=c0+zero; print*,sqrt(c0**2-r)
c0=(-0.0,0.5); c0=c0+zero; print*,sqrt(c0**2-r)
END PROGRAM sZ
Now the results are same. :)
However, I would like to know more on this. When are signed zeroes necessary?

Maximum value of 64 bit floating point number for overflow detection

I have a seemingly simple problem: I want to detect whether a floating point addition in Fortran will overflow by doing something like the following:
real*8 :: a, b, c
a = ! some value
b = ! some value
if (b > DOUBLE_MAX - a) then
! handle overflow
else
c = a + b
The problem is that I don't know what DOUBLE_MAX should be. I'm aware of how floating point numbers are represented according to IEEE 754 but the largest value representable by a double precision floating point number seems to be too large for a variable of type real*8 (i.e. if I try to assign 1.7976931348623157e+308 to such a variable gfortran complains). C and C++ have predefined constants/generic functions for this purpose but I couldn't find a Fortran equivalent.
Note: I'm aware that real*8 is not really part of the standard but there seems to be no other way to reliably specify that a floating point number should use the double precision format.
Something like this?
real(REAL64) function func( a, b )
use, intrinsic :: iso_fortran_env, only: REAL64, INT64
use, intrinsic :: ieee_arithmetic, only: ieee_value, ieee_set_flag, IEEE_OVERFLOW, IEEE_QUIET_NAN
implicit none
real(REAL64), intent(in) :: a, b
real(REAL64), parameter :: MAX64 = huge(0.0_REAL64)
if ( b > MAX64-a ) then
! Set IEEE_OVERFLOW flag and return NaN
call ieee_set_flag(IEEE_OVERFLOW,.true.)
func = ieee_value(func,IEEE_QUIET_NAN)
else
func = a + b
end if
return
end function func
All I could find for intrinsic ieee_exceptions module is:
https://github.com/gcc-mirror/gcc/blob/master/libgfortran/ieee/ieee_exceptions.F90
For setting NaN value see post.
There are likely better ways to detect overflow, but the precise answer to your question is to use the huge function. HUGE(a) returns the largest possible number representable by the type a.

Apparent mixed-mode arithmetic from a Fortran intrinsic function

What I'm doing is very straightforward. Here are the relevant declarations:
USE, INTRINSIC :: ISO_Fortran_env, dp=>REAL64 !modern DOUBLE PRECISION
REAL(dp), PARAMETER :: G_H2_alpha = 1.57D+04, G_H2_beta = 5.3D+03, G_H2_gamma = 4.5D+03
REAL(dp) :: E_total_alpha, E_total_beta, E_total_gamma, P_H2_sed
Usage:
P_H2_sed = G_H2_alpha * E_total_alpha + G_H2_beta * E_total_beta * G_H2_gamma * E_total_gamma
where E_total_alpha, E_total_beta, and E_total_gamma are just running dp totals inside various loops. I ask for the nearest integer NINT(P_H2_sed) and get -2147483648, which looks like mixed-mode arithmetic. The float P_H2_sed returns 2529548272025.4888, so I would expect NINT to return 2529548272026. I didn't think it was possible to get this kind of result from an intrinsic function. I haven't seen this since my days with the old F77 compiler. I'm doing something bad, but what is the question.
NINT, by default, returns an integer with default type parameter, that usually is equivalent to int32.
An integer of this kind cannot represent a number as high as 2529548272026. The maximum representable number is 2^31-1, that is 2147483647. The result you are getting is similar to that, but is the lowest representable number, -2147483648 (equivalent o all 32 bits set to 1).
To get a result of other kind from NINT, pass an optional parameter named kind, like this: NINT(P_H2_sed, kind=int64).

Determine Fortran derived type size in memory

The Fortran intrinsic function transfer can be used to covert a derived type into a real or integer array. This is potentially very useful when working in legacy systems which relies on arrays of primitive types (integer, real etc.) for persistence.
The code below runs at least on ifort and gfortran and converts a simple derived type example to an integer array (updated with solution):
program main
implicit none
integer, parameter :: int_mem_size = storage_size(1)
type subtype
integer a
double precision b
end type subtype
type :: mytype
integer :: foo
double precision :: bar
type(subtype) :: some_type
end type
type(mytype) :: my_var
type(subtype) :: my_subtype
! Old version: integer :: x(30)
integer, allocatable :: x(:)
integer :: mem_size
!Allocate array with required size
mem_size = storage_size(my_var)
allocate(x(mem_size/int_mem_size))
my_subtype%a = 1
my_subtype%b = 2.7
my_var%foo = 42
my_var%bar = 3.14
my_var%some_type = my_subtype
write(*,*) "transfering..."
x = transfer(my_var, x)
write(*,*) "Integer transformation:", x
end program main
On my PC, this is the output (this result is at least platform dependent):
transfering...
Integer transformation: 42 0 1610612736 1074339512
999 0 -1610612736 1074108825
My problem is that I have "guessed" that a 30 element long integer array is large enough to store this data structure. Is there a way I can determine how large the array needs to be to store the whole data structure?
If you have a Fortran 2008 compliant compiler, or one that is compliant enough, you will find the intrinsic function storage_size which returns the number of bits used to store its argument. Failing that most compilers that I am familiar with implement a non-standard function to do this; the Intel Fortran compiler has a function called sizeof which returns the number of bytes required to store its argument.

Result of GAMMA underflows its kind

I would like to calculate gamma(-170.1) using the program below:
program arithmetic
! program to do a calculation
real(8) :: x
x = GAMMA(-170.1)
print *, x
end program
but I get the error:
test.f95:4.10:
x = GAMMA(-170.1)
1
Error: Result of GAMMA underflows its kind at (1)
when I compile with gfortran. According to Maple gamma(-170.1) = 5.191963205*10^(-172) which I think should be within the range of the exponent of the variable x as I've defined it.
The below modification of your program should work. Remember that in Fortran the RHS is evaluated before assigning to the LHS, and that floating point literals are of default kind, that is single precision. Thus, making the argument to GAMMA double precision the compiler chooses the double precision GAMMA.
program arithmetic
! program to do a calculation
integer, parameter :: dp = kind(1.0d0)
real(dp) :: x
x = GAMMA(-170.1_dp)
print *, x
end program
-170.0 may be treated as a float. If so, changing it to a double should resolve the issue.