Hello, I’m writing an higher level interface to some integration subroutines (as exercise) and was wondering how can I represent infinity and negative infinity in Moderno Fortran. That’s what I’m trying to accomplish:
program main
implicit none
real :: a, b
a = -infinity
b = +infinity
! call integrate(f, a, b, ...
end program
program ieee
use, intrinsic :: iso_fortran_env, only: real64, int64
use, intrinsic :: ieee_arithmetic
implicit none
real(real64) :: r, one
integer(int64) :: i
one = 1.0_real64
r = ieee_value(one, ieee_positive_inf)
print *, r
i = transfer(r, i)
print '(b64.64)', i
print *, one / r
i = transfer(one/r, i)
print '(b64.64)', i
print *
r = ieee_value(one, ieee_negative_inf)
print *, r
i = transfer(r, i)
print '(b64.64)', i
print *, one / r
i = transfer(one/r, i)
print '(b64.64)', i
print *
end program ieee
program test ! demonstrate setting and reading infinity
implicit none
integer, parameter :: wp = kind(1.0d0)
real(kind=wp), parameter :: infin = 2*huge(1.0d0)
real(kind=wp) :: x
character (len=20) :: text
print*,infinity(),infin,infin>huge(1.0d0)
text = "Infinity"
read (text,*) x
print*,x
text = "+Inf"
read (text,*) x
print*,x
contains
real(kind=wp) function infinity()
implicit none
real(kind=wp) :: x
x = huge(1.0_wp)
infinity = x + x
end function infinity
end program test
gives output +Inf +Inf T for g95 and the same for gfortran and Intel Fortran, although they output Infinity instead of +Inf. The program also shows that one can read infinity from a string.
In the NLopt optimization library, the documentations suggests to use \pmhuge(x) for unbounded dimensions. It kind of makes sense that you would only integrate from/to the largest value which is still representable.