gfortran compiler Error: result of exponentiation exceeds the range of INTEGER(4) - gcc

I have this line in fortran and I'm getting the compiler error in the title. dFeV is a 1d array of reals.
dFeV(x)=R1*5**(15) * (a**2) * EXP(-(VmigFe)/kbt)
for the record, the variable names are inherited and not my fault. I think this is an issue with not having the memory space to compute the value on the right before I store it on the left as a real (which would have enough room), but I don't know how to allocate more space for that computation.

The problem arises as one part of your computation is done using integer arithmetic of type integer(4).
That type has an upper limit of 2^31-1 = 2147483647 whereas your intermediate result 5^15 = 30517578125 is slightly larger (thanks to #evets comment).
As pointed out in your question: you save the result in a real variable.
Therefor, you could just compute that exponentiation using real data types: 5.0**15.
Your formula will end up like the following
dFeV(x)= R1 * (5.0**15) * (a**2) * exp(-(VmigFe)/kbt)
Note that integer(4) need not be the same implementation for every processor (thanks #IanBush).
Which just means that for some specific machines the upper limit might be different from 2^31-1 = 2147483647.

As indicated in the comment, the value of 5**15 exceeds the range of 4-byte signed integers, which are the typical default integer type. So you need to instruct the compiler to use a larger type for these constants. This program example shows one method. The ISO_FORTRAN_ENV module provides the int64 type. UPDATE: corrected to what I meant, as pointed out in comments.
program test_program
use ISO_FORTRAN_ENV
implicit none
integer (int64) :: i
i = 5_int64 **15_int64
write (*, *) i
end program

Although there does seem to be an additional point here that may be specific to gfortran:
integer(kind = 8) :: result
result = 5**15
print *, result
gives: Error: Result of exponentiation at (1) exceeds the range of INTEGER(4)
while
integer(kind = 8) :: result
result = 5**7 * 5**8
print *, result
gives: 30517578125
i.e. the exponentiation function seems to have an integer(4) limit even if the variable to which the answer is being assigned has a larger capacity.

Related

drand and drandm in fortran are giving numbers outside of [0,1] range

here is my script below, I use implicit none because I would like to eventually implement them in a bigger program with more variables.
program testdrandm
implicit none
real, external :: drand, drandm, rand
print *, 'drand', drand(0), drand(0)
print *, 'drandm', drandm(0), drandm(0)
print *, 'rand', rand(0), rand(0)
end program testdrandm
here is my output:
drand 4.3290930E-39 -686.1465
drandm -8.9381798E+10 1.7946890E+19
rand 0.9679557 0.1896898
The first number is within range but extremely small and will give me zero values when I use it to multiply other values. Rand works but I would like to use drandm. I would like to get random numbers between 0 to 1. Please let me know if I am using this function incorrectly.
You should use the intrinsic random_seed and random_number to generate random numbers in Fortran. The intrinsic random_number will give you real number(s) between 0 and 1.
See e.g.:
https://gcc.gnu.org/onlinedocs/gfortran/RANDOM_005fSEED.html#RANDOM_005fSEED
https://gcc.gnu.org/onlinedocs/gfortran/RANDOM_005fNUMBER.html#RANDOM_005fNUMBER
#tim18 touched on the answer, but you might not have picked up on exactly WHY you got these results.
I modified the program to print the hex representation of the values returned. When run using ifort, I get:
drand 00000000002F23C0 00000000C42B8960
drandm 00000000D1A67C90 000000005F791029
rand 000000003F77CBF2 000000003E423E09
IEEE double precision is an 8-byte format, and drand/drandm return 8 bytes, but you declared them as real (single precision), so you get only the low 4 bytes and NOT a conversion. Because the size of the exponent field is different between these types (8 bits vs. 11 bits), interpreting the low 4 bytes of a double as a real will get you wrong values.
Now see what happens if I declare drand and drandm as double precision:
drand 3EF791E0002F23C0 3FB5C4AFC42B8960
drandm 3FE33E47D1A67C90 3FEC88145F791029
rand 000000003F77CBF2 000000003E423E09
or if I go back to list-directed:
drand 2.247793601009899E-005 8.503244914348818E-002
drandm 0.601352605317418 0.891611277075303
rand 0.9679557 0.1896898
Better?
That said, I wholly agree with those who suggest using RANDOM_NUMBER instead. You would not have seen this sort of problem if you used the intrinsic procedure.

MT19937 does NOT reproduce the same pseudo-random sequence by holding the seed value a constant

I'm writing a checkpoint function in my Monte Carlo simulation in Fortran 90/95, the compiler I'm using is ifort 18.0.2, before going through detail just to clarify the version of pseudo-random generator I'm using:
A C-program for MT19937, with initialization, improved 2002/1/26.
Coded by Takuji Nishimura and Makoto Matsumoto.
Code converted to Fortran 95 by Josi Rui Faustino de Sousa
Date: 2002-02-01
See mt19937 for the source code.
The general structure of my Monte Carlo simulation code is given below:
program montecarlo
call read_iseed(...)
call mc_subroutine(...)
end
Within the read_iseed
subroutine read_iseed(...)
use mt19937
if (Restart == 'n') then
call system('od -vAn -N4 -td4 < /dev/urandom > '//trim(IN_ISEED)
open(unit=7,file=trim(IN_ISEED),status='old')
read(7,*) i
close(7)
!This is only used to initialise the PRNG sequence
iseed = abs(i)
else if (Restart == 'y') then
!Taking seed value from the latest iteration of previous simulation
iseed = RestartSeed
endif
call init_genrand(iseed)
print *, 'first pseudo-random value ',genrand_real3(), 'iseed ',iseed
return
end subroutine
Based on my understanding, if the seed value holds a constant, the PRNG should be able to reproduce the pseudo-random sequence every time?
In order to prove this is the case, I ran two individual simulations by using the same seed value, they are able to reproduce the exact sequence. So far so good!
Based on the previous test, I'd further assume that regardless the number of times init_genrand() being called within one individual simulation, the PRNG should also be able to reproduce the pseudo-random value sequence? So I did a little modification to my read_iseed() subroutine
subroutine read_iseed(...)
use mt19937
if (Restart == 'n') then
call system('od -vAn -N4 -td4 < /dev/urandom > '//trim(IN_ISEED)
open(unit=7,file=trim(IN_ISEED),status='old')
read(7,*) i
close(7)
!This is only used to initialise the PRNG sequence
iseed = abs(i)
else if (Restart == 'y') then
!Taking seed value from the latest iteration of the previous simulation
iseed = RestartSeed
endif
call init_genrand(iseed)
print *, 'first time initialisation ',genrand_real3(), 'iseed ',iseed
call init_genrand(iseed)
print *, 'second time initialisation ',genrand_real3(), 'iseed ',iseed
return
end subroutine
The output is surprisingly not the case I thought would be, by all means iseed outputs are identical in between two initializations, however, genrand_real3() outputs are not identical.
Because of this unexpected result, I struggled with resuming the simulation at an arbitrary state of the system since the simulation is not reproducing the latest configuration state of the system I'm simulating.
I'm not sure if I've provided enough information, please let me know if any part of this question needs to be more specific?
From the source code you've provided (See [mt19937]{http://web.mst.edu/~vojtat/class_5403/mt19937/mt19937ar.f90} for the source code.), the init_genrand does not clear the whole state.
There are 3 critical state variables:
integer( kind = wi ) :: mt(n) ! the array for the state vector
logical( kind = wi ) :: mtinit = .false._wi ! means mt[N] is not initialized
integer( kind = wi ) :: mti = n + 1_wi ! mti==N+1 means mt[N] is not initialized
The first one is the "array for the state vector", second one is a flag that ensures we don't start with uninitialized array, and the third one is some position marker, as I guess from the condition stated in the comment.
Looking at subroutine init_genrand( s ), it sets mtinit flag, and fills the mt() array from 1 upto n. Alright.
Looking at genrand_real3 it's based on genrand_int32.
Looking at genrand_int32, it starts up with
if ( mti > n ) then ! generate N words at one time
! if init_genrand() has not been called, a default initial seed is used
if ( .not. mtinit ) call init_genrand( seed_d )
and does its arithmetic magic and then starts getting the result:
y = mt(mti)
mti = mti + 1_wi
so.. mti is a positional index in the 'state array', and it is incremented by 1 after each integer read from the generator.
Back to init_genrand - remember? it have been resetting the array mt() but it has not resetted the MTI back to its starting mti = n + 1_wi.
I bet this is the cause of the phenomenon you've observed, since after re-initializing with the same seed, the array would be filled with the same set of values, but later the int32 generator would read from a different starting point. I doubt it was intended, so it's probably a tiny bug easy to overlook.

Too large const on Arduino UNO

I'm trying to execute an algorithm on an Arduino UNO, it needs const table with some larges numbers and sometimes, I get overflow values. This is the case for this number : 628331966747.0
Okay, this is a big one, but its type is float (32 bit) where maximum is 3.4028235e38. So it should work, theoretically ?
What can I do against this ? Do you know a solution ?
EDIT : On Arduino UNO, double are exaclty the same type that floats (32 bits)
Here is a code that leads to the error :
float A;
void setup() {
A = 628331966747.0;
Serial.begin(9600);
}
void loop() {
Serial.println(A);
delay(1000);
}
it print "ovf, ovf, ..., ovf"
There is nothing wrong with the constant itself (except for its rather optimistic number of significant figures), but the problem is with the implementation of the Arduino's library support for printing floating point values. Print::printFloat() contains the following pre-condition tests:
if (isnan(number)) return print("nan");
if (isinf(number)) return print("inf");
if (number > 4294967040.0) return print ("ovf"); // constant determined empirically
if (number <-4294967040.0) return print ("ovf"); // constant determined empirically
It seems that the range of printable values is deliberately restricted in order presumably to reduce complexity and code size. The subsequent code reveals why:
// Extract the integer part of the number and print it
unsigned long int_part = (unsigned long)number;
double remainder = number - (double)int_part;
n += print(int_part);
The somewhat simplistic implementation requires that the absolute value of the integer part is itself a 32bit integer.
The worrying thing perhaps is the comment "constant determined empirically" which rather suggests that the values were arrived at by trial and error rather then an understanding of the mathematics! One has to wonder why these values are not defined in terms of INT_UMAX.
There is a proposed "fix" described here, but it will not work at least because it applies the integer abs() function to the double parameter number, which will only work if the integer part is less than the even more restrictive MAX_INT. The author has posted a link to a zip file containing a fix that looks more likely to work (there is evidence at least of testing!).

Passing user-defined variables using MPI [duplicate]

I have a Fortran program where I specify the kind of the numeric data types in an attempt to retain a minimum level of precision, regardless of what compiler is used to build the program. For example:
integer, parameter :: rsp = selected_real_kind(4)
...
real(kind=rsp) :: real_var
The problem is that I have used MPI to parallelize the code and I need to make sure the MPI communications are specifying the same type with the same precision. I was using the following approach to stay consistent with the approach in my program:
call MPI_Type_create_f90_real(4,MPI_UNDEFINED,rsp_mpi,mpi_err)
...
call MPI_Send(real_var,1,rsp_mpi,dest,tag,MPI_COMM_WORLD,err)
However, I have found that this MPI routine is not particularly well-supported for different MPI implementations, so it's actually making my program non-portable. If I omit the MPI_Type_create routine, then I'm left to rely on the standard MPI_REAL and MPI_DOUBLE_PRECISION data types, but what if that type is not consistent with what selected_real_kind picks as the real type that will ultimately be passed around by MPI? Am I stuck just using the standard real declaration for a datatype, with no kind attribute and, if I do that, am I guaranteed that MPI_REAL and real are always going to have the same precision, regardless of compiler and machine?
UPDATE:
I created a simple program that demonstrates the issue I see when my internal reals have higher precision than what is afforded by the MPI_DOUBLE_PRECISION type:
program main
use mpi
implicit none
integer, parameter :: rsp = selected_real_kind(16)
integer :: err
integer :: rank
real(rsp) :: real_var
call MPI_Init(err)
call MPI_Comm_rank(MPI_COMM_WORLD,rank,err)
if (rank.eq.0) then
real_var = 1.123456789012345
call MPI_Send(real_var,1,MPI_DOUBLE_PRECISION,1,5,MPI_COMM_WORLD,err)
else
call MPI_Recv(real_var,1,MPI_DOUBLE_PRECISION,0,5,MPI_COMM_WORLD,&
MPI_STATUS_IGNORE,err)
end if
print *, rank, real_var
call MPI_Finalize(err)
end program main
If I build and run with 2 cores, I get:
0 1.12345683574676513672
1 4.71241976735884452383E-3998
Now change the 16 to a 15 in selected_real_kind and I get:
0 1.1234568357467651
1 1.1234568357467651
Is it always going to be safe to use selected_real_kind(15) with MPI_DOUBLE_PRECISION no matter what machine/compiler is used to do the build?
Use the Fortran 2008 intrinsic STORAGE_SIZE to determine the number bytes that each number requires and send as bytes. Note that STORAGE_SIZE returns the size in bits, so you will need to divide by 8 to get the size in bytes.
This solution works for moving data but does not help you use reductions. For that you will have to implement a user-defined reduction operation. If that's important to you, I will update my answer with the details.
For example:
program main
use mpi
implicit none
integer, parameter :: rsp = selected_real_kind(16)
integer :: err
integer :: rank
real(rsp) :: real_var
call MPI_Init(err)
call MPI_Comm_rank(MPI_COMM_WORLD,rank,err)
if (rank.eq.0) then
real_var = 1.123456789012345
call MPI_Send(real_var,storage_size(real_var)/8,MPI_BYTE,1,5,MPI_COMM_WORLD,err)
else
call MPI_Recv(real_var,storage_size(real_var)/8,MPI_BYTE,0,5,MPI_COMM_WORLD,&
MPI_STATUS_IGNORE,err)
end if
print *, rank, real_var
call MPI_Finalize(err)
end program main
I confirmed that this change corrects the problem and the output I see is:
0 1.12345683574676513672
1 1.12345683574676513672
Not really an answer, but we have the same problem and use something like this:
!> Number of digits for single precision numbers
integer, parameter, public :: single_prec = 6
!> Number of digits for double precision numbers
integer, parameter, public :: double_prec = 15
!> Number of digits for extended double precision numbers
integer, parameter, public :: xdble_prec = 18
!> Number of digits for quadruple precision numbers
integer, parameter, public :: quad_prec = 33
integer, parameter, public :: rk_prec = double_prec
!> The kind to select for default reals
integer, parameter, public :: rk = selected_real_kind(rk_prec)
And then have an initialization routine where we do:
!call mpi_type_create_f90_real(rk_prec, MPI_UNDEFINED, rk_mpi, iError)
!call mpi_type_create_f90_integer(long_prec, long_k_mpi, iError)
! Workaround shitty MPI-Implementations.
select case(rk_prec)
case(single_prec)
rk_mpi = MPI_REAL
case(double_prec)
rk_mpi = MPI_DOUBLE_PRECISION
case(quad_prec)
rk_mpi = MPI_REAL16
case default
write(*,*) 'unknown real type specified for mpi_type creation'
end select
long_k_mpi = MPI_INTEGER8
While this is not nice, it works reasonably well, and seems to be usable on Cray, IBM BlueGene and conventional Linux Clusters.
Best thing to do is push sites and vendors to properly support this in MPI. As far as I know it has been fixed in OpenMPI and planned to be fixed in MPICH by 3.1.1. See OpenMPI Tickets 3432 and 3435 as well as MPICH Tickets 1769 and 1770.
How about:
integer, parameter :: DOUBLE_PREC = kind(0.0d0)
integer, parameter :: SINGLE_PREC = kind(0.0e0)
integer, parameter :: MYREAL = DOUBLE_PREC
if (MYREAL .eq. DOUBLE_PREC) then
MPIREAL = MPI_DOUBLE_PRECISION
else if (MYREAL .eq. SINGLE_PREC) then
MPIREAL = MPI_REAL
else
print *, "Erorr: Can't figure out MPI precision."
STOP
end if
and use MPIREAL instead of MPI_DOUBLE_PRECISION from then on.

Convert Enum to Binary (via Integer or something similar)

I have an Ada enum with 2 values type Polarity is (Normal, Reversed), and I would like to convert them to 0, 1 (or True, False--as Boolean seems to implicitly play nice as binary) respectively, so I can store their values as specific bits in a byte. How can I accomplish this?
An easy way is a lookup table:
Bool_Polarity : constant Array(Polarity) of Boolean
:= (Normal=>False, Reversed => True);
then use it as
B Boolean := Bool_Polarity(P);
Of course there is nothing wrong with using the 'Pos attribute, but the LUT makes the mapping readable and very obvious.
As it is constant, you'd like to hope it optimises away during the constant folding stage, and it seems to: I have used similar tricks compiling for AVR with very acceptable executable sizes (down to 0.6k to independently drive 2 stepper motors)
3.5.5 Operations of Discrete Types include the function S'Pos(Arg : S'Base), which "returns the position number of the value of Arg, as a value of type universal integer." Hence,
Polarity'Pos(Normal) = 0
Polarity'Pos(Reversed) = 1
You can change the numbering using 13.4 Enumeration Representation Clauses.
...and, of course:
Boolean'Val(Polarity'Pos(Normal)) = False
Boolean'Val(Polarity'Pos(Reversed)) = True
I think what you are looking for is a record type with a representation clause:
procedure Main is
type Byte_T is mod 2**8-1;
for Byte_T'Size use 8;
type Filler7_T is mod 2**7-1;
for Filler7_T'Size use 7;
type Polarity_T is (Normal,Reversed);
for Polarity_T use (Normal => 0, Reversed => 1);
for Polarity_T'Size use 1;
type Byte_As_Record_T is record
Filler : Filler7_T;
Polarity : Polarity_T;
end record;
for Byte_As_Record_T use record
Filler at 0 range 0 .. 6;
Polarity at 0 range 7 .. 7;
end record;
for Byte_As_Record_T'Size use 8;
function Convert is new Ada.Unchecked_Conversion
(Source => Byte_As_Record_T,
Target => Byte_T);
function Convert is new Ada.Unchecked_Conversion
(Source => Byte_T,
Target => Byte_As_Record_T);
begin
-- TBC
null;
end Main;
As Byte_As_Record_T & Byte_T are the same size, you can use unchecked conversion to convert between the types safely.
The representation clause for Byte_As_Record_T allows you to specify which bits/bytes to place your polarity_t in. (i chose the 8th bit)
My definition of Byte_T might not be what you want, but as long as it is 8 bits long the principle should still be workable. From Byte_T you can also safely upcast to Integer or Natural or Positive. You can also use the same technique to go directly to/from a 32 bit Integer to/from a 32 bit record type.
Two points here:
1) Enumerations are already stored as binary. Everything is. In particular, your enumeration, as defined above, will be stored as a 0 for Normal and a 1 for Reversed, unless you go out of your way to tell the compiler to use other values.
If you want to get that value out of the enumeration as an Integer rather than an enumeration value, you have two options. The 'pos() attribute will return a 0-based number for that enumeration's position in the enumeration, and Unchecked_Conversion will return the actual value the computer stores for it. (There is no difference in the value, unless an enumeration representation clause was used).
2) Enumerations are nice, but don't reinvent Boolean. If your enumeration can only ever have two values, you don't gain anything useful by making a custom enumeration, and you lose a lot of useful properties that Boolean has. Booleans can be directly selected off of in loops and if checks. Booleans have and, or, xor, etc. defined for them. Booleans can be put into packed arrays, and then those same operators are defined bitwise across the whole array.
A particular pet peeve of mine is when people end up defining themselves a custom boolean with the logic reversed (so its true condition is 0). If you do this, the ghost of Ada Lovelace will come back from the grave and force you to listen to an exhaustive explanation of how to calculate Bernoulli sequences with a Difference Engine. Don't let this happen to you!
So if it would never make sense to have a third enumeration value, you just name objects something appropriate describing the True condition (eg: Reversed_Polarity : Boolean;), and go on your merry way.
It seems all I needed to do was pragma Pack([type name]); (in which 'type name' is the type composed of Polarity) to compress the value down to a single bit.

Resources