How to assign bit-pattern Z'FEDCBA09' to a 32bit integer - fortran

How can I assign the boz-literal-constant Z'FEDCBA09' or any other bit-pattern with the most-significant bit equal to 1 to an integer?
The standard states:
INT(A[,KIND]): If A is a boz-literal-constant, the value of the result is the value whose bit sequence according to the model in 16.3 is the same as that of A as modified by padding or truncation according to 16.3.3. The interpretation of a bit sequence whose most significant bit is 1 is processor dependent.
source: Fortran 2018 Standard
So the following assignments might fail (assume integer is default 32 bit):
program boz
implicit none
integer :: x1 = int(Z'FEDCBA09')
integer :: x2 = int(Z'FFFFFFFF')
integer :: x3
data x3/Z'FFFFFFFF'/
end program
Using gfortran, this will only work when adding -fno-range-check but this introduces extra unwanted effects:
-fno-range-check: Disable range checking on results of simplification of constant expressions during compilation. For example, GNU Fortran will give an error at compile time when simplifying a = 1. / 0. With this option, no error will be given and a will be assigned the value +Infinity. If an expression evaluates to a value outside of the relevant range of [-HUGE():HUGE()], then the expression will be replaced by -Inf or +Inf as appropriate. Similarly, DATA i/Z'FFFFFFFF'/ will result in an integer overflow on most systems, but with -fno-range-check the value will "wrap around" and i will be initialized to -1 instead.
source: GNU Compiler Collection, gfortran manual
I attempted the following, which works fine but still not 100%
integer(kind=INT32) :: x1 = transfer(real(Z'FEDCBA09',kind=REAL32),1_INT32)
integer(kind=INT32) :: x1 = transfer(real(Z'FFFFFFFF',kind=REAL32),1_INT32)
The latter case fails with gfortran as it complains that Z'FFFFFFFF' represents NaN.
Using IOR(0,Z'FEDCBA09') also fails as it converts the boz-literal using INT
Question: How can you robustly assign a bit pattern using a boz-literal-constant? That is to say, independent of the used compiler (GNU, SUN, PGI, NAG, ...).
Answer: The most robust answer is currently given by Jim Rodes in this comment:
x = ior(ishft(int(Z'FEDC'),bit_size(x)/2),int(Z'BA09'))
This will work on any compiler and does not require any other data-type to be successful.

The need for -fno-range-check has been removed in what will be gfortran 10.1 when it is released. In 10.1, the bit patterns you have specified will be treated as if they are 32-bit unsigned integers and twos-complement wrap-around semantics are enforced.
Your first code snippet with a print statement added
program boz
implicit none
integer :: x1 = int(Z'FEDCBA09')
integer :: x2 = int(Z'FFFFFFFF')
integer :: x3
data x3/Z'FFFFFFFF'/
print *, x1, x2, x3
end program
yields
$ gfortran -o z file.f90
$ ./z
-19088887 -1 -1
and does not require the -fno-range-check option. The same goes for the proposed transfer method:
program boz
use iso_fortran_env
implicit none
integer(kind=INT32) :: x1 = &
& transfer(real(Z'FEDCBA09',kind=REAL32),1_INT32)
integer(kind=INT32) :: x2 = &
& transfer(real(Z'FFFFFFFF',kind=REAL32),1_INT32)
print '(I0,1X,Z8.8)', x1, x1
print '(I0,1X,Z8.8)', x2, x2
end program
returning:
$ gfortran -o z file.f90
$ ./z
-19088887 FEDCBA09
2143289344 7FC00000
Note: gfortran converts sNaN into qNan, which is a bug but no one cares.

If you are stuck with an older version of gfortran, then with the
integer case you need to use an intermediate conversion
program boz
use iso_fortran_env
implicit none
integer(kind=INT32) :: x1 = &
& transfer(int(Z'FEDCBA09',kind=INT64),1_INT32)
print '(I0,1X,Z8.8)', x1, x1
end program
gfortran will constant fold the statement with transfer. You can verify this by looking at the file created with the -fdump-tree-original option. For both this answer and the previous one, the command line is simple gfortran -o z file.f90.

When dealing with languages that do not support unsigned integers and you need to be able to test and/or set the high bit of the largest available integer, you can split the value into 2 variables and deal with the high order and low order bits separately.
One method would be to put the upper half into one variable and the lower half into another so that:
integer :: x1 = int(Z'FEDCBA09')
becomes:
integer :: x1Hi = int(Z'FEDC')
integer :: x1Lo = int(Z'BA09')
As the OP pointed out in an edit, a shift operation could then be used to assign the full value to a single variable like this. I changed it slightly so that it would work in case x is more than 32 bits.
x = ior(ishft(int(Z'FEDC'), 16), int(Z'BA09'))
Another possible method would be to have a separate variable for just the high bit.

I have asked a similar question before at comp.lang.fortran: https://in.memory.of.e.tern.al/comp.lang.fortran/thread/3878931
A practically usable, even though still the 100% probability was still questioned by some (see there) was just to use the reverse BOZ constant/string and NOT() it.
Instead of
integer, parameter :: i = Z'A0000000'
use
integer, parameter :: i = NOT(int(Z'5FFFFFFF'))
The analysis in the link goes to a large detail and to fine points of the standard and the numeric model interpretation.
Since then I use this in my production code: https://bitbucket.org/LadaF/elmm/src/master/src/rng_par_zig.f90 line 285 which is a translation of http://vigna.di.unimi.it/xorshift/xorshift128plus.c

Related

Solving linear equations on Fortran using LAPACK [duplicate]

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.

Use CEILING Without the Effect of Rounding Error

I'm trying to use the intrinsic function ‘CEILING’, but the rounding error makes it difficult to get what I want sometimes. The sample code is just very simple:
PROGRAM MAIN
IMPLICIT NONE
INTEGER, PARAMETER :: ppm_kind_double = KIND(1.0D0)
REAL(ppm_kind_double) :: before,after,dx
before = -0.112
dx = 0.008
after = CEILING(before/dx)
WRITE(*,*) before, dx, before/dx, after
END
And I got results:
The value I give to 'before' and 'dx' in the code is just for demonstration. For those before/dx = -13.5 for example, I want to use CEILING to get -13. But for the picture I show, I actually want to get -14. I have considered using some arguments like
IF(ABS(NINT(before/dx) - before/dx) < 0.001)
But that's simply not beautiful. Is there any better way to do this?
Update:
I was surprised to find that the problem won't occur if I set the variables to constants in ppm_kind_double. So I guess this 'rounding error' will only happen when the number of digits for rounding accuracy of the machine I use is more than what's defined in ppm_kind_double. I actually run my program(not this demo code) on a cluster, which I don't know about the machine precision. So maybe it's quad precision on that machine that leads to the problem?
After I set constants to double precision:
before = -0.112_ppm_kind_double
dx = 0.008_ppm_kind_double
This is a bit tricky, because you never know where the rounding error comes from. If dx was just a tiny bit larger than 0.008 then the division before/dx might still be rounded to the same value, but now -13 would be the correct answer.
That said, the most common method around that that I have seen is to just nudge the previous value ever so little into the opposite direction. Something like this:
program sign_test
use iso_fortran_env
implicit none
real(kind=real64) :: a, b
integer(kind=int32) :: c
a = -0.112
b = 0.008
c = my_ceiling(a/b)
print*, a, b, c
contains
function my_ceiling(v)
implicit none
real(kind=real64), intent(in) :: v
integer(kind=int32) :: my_ceiling
my_ceiling = ceiling(v - 1d-6, kind=int32)
end function my_ceiling
end program sign_test
This won't have any impact on the vast majority of values, but there are now a few values that will get rounded up by more than intended.
note if your reals are notionally "exact" to a specified precision you might do something like this:
after=nint(1000*before)/nint(1000*dx)
this works for your example.. you haven't said what you'd expect for both values positive and so on so you might need to work it a bit.

Error with parentheses when assigning to complex variable

I have the following set of commands in my Fortran code:
COMPLEX*16, DIMENSION(4,1) :: INSTATE_BASISSTATES
INSTATE_BASISSTATES(:,:) = (0.0D0,0.0D0)
INSTATE_BASISSTATES(1,1) = ((1.0D0/SQRT(2)),0.0D0)
INSTATE_BASISSTATES(3,1) = ((1.0D0/SQRT(2)),0.0D0)
When I run/compile the program using gfortran on cygwin, I get the error
INSTATE_BASISSTATES(1,1) = (1.0D0/DREAL(SQRT(2.0D0)),0.0D0)
1
Error: Expected a right parenthesis in expression at (1)
INSTATE_BASISSTATES(3,1) = (1.0D0/DREAL(SQRT(2.0D0)),0.0D0)
1
Error: Expected a right parenthesis in expression at (1)
What could be the issue? Aren't my brackets correct?
On the right hand side of the assignment statement you are trying to use a complex literal constant. However,
(1.0D0/DREAL(SQRT(2.0D0)),0.0D0)
isn't a valid form for such a constant.
For a complex literal, the real and imaginary components must be either named constants or literal constants. 1.0D0/DREAL(SQRT(2.0D0)) is neither of those things. For the line where you had no complaint, both components of (0.0D0,0.0D0) are literal constants.
As in this other answer you could make a named constant with the value wanted and use that. Alternatively, as you are just doing a boring assignment (which doesn't have various restrictions which apply to initialization, etc.,) you can use the cmplx intrinsic to return a complex value
INSTATE_BASISSTATES(1,1) = CMPLX(1.0D0/DREAL(SQRT(2.0D0)),0.0D0)
Here the real and imaginary components don't need to be constants. You could even note that
INSTATE_BASISSTATES(1,1) = CMPLX(1.0D0/DREAL(SQRT(2.0D0)))
works just as well: if the imaginary component value isn't provided, the returned complex has imaginary component zero.
There is a slight complication, though. cmplx by default returns a complex number with kind of the default real. To return something matching complex*16 (which isn't standard Fortran, but let's assume it corresponds to double precision) you'll need CMPLX(..., [...], KIND=KIND(0d0)) (or KIND=KIND(INSTATE_BASISSTATES))
As a side note, as Vladimir F comments dreal isn't standard Fortran. You could use dble, or real with a suitable kind number. But we can also see that sqrt(2d0) already returns a double precision real, so even those are redundant: 1/sqrt(2d0) has the same (mathematical) result as the original more cumbersome expression. As do 2d0**(-0.5) and sqrt(2d0)/2.
You could even replace the right hand side with
SQRT((5d-1,0))
as we see that sqrt also accepts a complex argument (in this case a complex literal constant). This form also avoids the awkwardness of the kind= specifier: its value has kind as well as type of the argument.
this is indeed "by design", one could define the constant of interest first and then use it in the initialization. For example:
COMPLEX*16, DIMENSION(4,1) :: INSTATE_BASISSTATES
REAL*8, PARAMETER :: my_const = 1D0 / SQRT(2D0)
INSTATE_BASISSTATES(:,:) = (0.0D0,0.0D0)
INSTATE_BASISSTATES(1,1) = (my_const,0.0D0)
INSTATE_BASISSTATES(3,1) = (my_const,0.0D0)
However, the statement REAL*8, PARAMETER :: my_const = 1D0 / SQRT(2D0) seems to require at least Fortran2003 standard, otherwise, following error is produced Elemental function as initialization expression with non-integer/non-character arguments. One can specify the standard with gfortran with -std=f2003 although it should be probably active by default.
#J123 still hasn't answered the pressing question. Are you writing your code in fixed-form format with .f extension or free-form .f90? Also, what version of gfortran are you using? I've posted a complete fix below. You can foliate your arrays by direct assignment using named parameter constants, or as the return value of the intrinsic transformational function cmplx. Please note the liberal use of the kind parameter wp to control the floating-point precision.
program main
use iso_fortran_env, only: &
wp => REAL64, & ! Or REAL128 if your architecture supports it
compiler_version, &
compiler_options
! Explicit typing only
implicit none
! Variable declarations
complex(wp) :: instate_basisstates(4,1)
real (wp), parameter :: ZERO = 0 ! Assigning integers is safe
real (wp), parameter :: SQRT2 = sqrt(2.0_wp)
real (wp), parameter :: ONE_OVER_SQRT2 = 1.0_wp/SQRT2
! Executable statements
instate_basisstates(:,:) = ZERO
instate_basisstates(1,1) = (ONE_OVER_SQRT2, ZERO)
instate_basisstates(3,1) = cmplx(1.0_wp/sqrt(2.0_wp), 0.0_wp, kind=wp)
print '(/4a/)', &
'This file was compiled using ', compiler_version(), &
' using the options ', compiler_options()
end program main
This yields:
This file was compiled using GCC version 6.1.1 20160802 using the options -mtune=generic -march=x86-64 -O3 -Wall -std=f2008ts

Fortran DO loop, warning to use integer only

I installed gfortran on my Ubuntu 15.04 system. While compiling Fortran code, the DO loop asks to take integer parameters only and not real values or variables. That includes the loop variable and the step expression. Why can't it take real values too?
The following is a program taken from here, exercise 3.5 of the section nested do loops.
program xytab
implicit none
!constructs a table of z=x/y for values of x from 1 to 2 and
!y from 1 to 4 in steps of .5
real :: x, y, z
print *, ' x y z'
do x = 1,2
do y = 1,4,0.5
z = x/y
print *, x,y,z
end do
end do
end program xytab
The error shown after compiling is:
xytab.f95:8.4:
do y = 1,4,0.5
1
Warning: Deleted feature: Loop variable at (1) must be integer
xytab.f95:8.12:
do y = 1,4,0.5
1
Warning: Deleted feature: Step expression in DO loop at (1) must be integer
xytab.f95:7.3:
do x = 1,2
1
Warning: Deleted feature: Loop variable at (1) must be integer
The Fortran standard now requires that a do construct's loop control is given by (scalar) integer expressions and that the loop variable is a (scalar) integer variable. The loop control consists of the start, step, and stop expressions (your step expression is 0.5). See R818 and R819 (8.1.6.2) of the Fortran 2008 document. That, then, is the short and simple answer: the standard says so.
It's a little more complicated than that, as the messages from the compiler suggest. Using other forms for loop control was present in Fortran up until Fortran 95. That is, from Fortran 95 onward using real expressions is a deleted feature.
What harm is there in using real expressions? Used correctly, one could imagine, there is no harm. But there's real difficulty in portability with them.
Consider
do x=0., 1., 0.1
...
end do
How many iterations? That would be (under the rules of Fortran 90) MAX(INT((m2 – m1 + m3) / m3), 0) where (m1 is the start value (0.), m2 the stop value (1.) and m3 the step value (0.1)). Is that 10 or 11 (or even 9)? It depends entirely on your numeric representation: we recall that 0.1 may not be exactly representable as a real number and INT truncates in converting to integer. You'd also have to worry about repeated addition of real numbers.
So, use integers and do some arithmetic inside the loop
do y_loop = 0, 6
y = 1 + y_loop/2.
...
end do
or
y = 1
do
if (y>4) exit
...
y = y+0.5
end do
Finally, you mention .f90 and .f95 file suffixes. gfortran doesn't take the first to mean that the source code follows the Fortran 90 standard (where the code would be fine). Further, the messages from the compiler are merely warnings, and these can be suppressed using the -std=legacy option. Conversely, using -std=f95 (or later standards) these become errors.
As a bonus fun fact consider the following piece of Fortran 90 code.
real y
integer i
loop_real: do y=1, 4, 0.5
end do loop_real
loop_integer: do i=1, 4, 0.5
end do loop_integer
While the loop named loop_real is valid, that named loop_integer isn't. In the calculation of the iteration count the three expressions are converted to the kind, with kind parameters, of the loop variable. INT(0.5) is 0.

fortran 64 bit hex BOZ

in C++ this is accepted:
uint64_t mask = 0x7FC0000FF80001FFLL;
but in fortran
integer(kind=8), parameter :: mask = Z'7FC0000FF80001FF'
does not work with gfortan.
I think both of them are 64bit values? or not?
gfortran complains:
arithmetic overflow from converting INTEGER(16) to INTEGER(8)
EDIT:
So, sorry for the confusion, here is some more extended problem description.
I will do some bit shifting in Fortran and have some sample code in c++.
There in the sample c++ code the masks are defines like:
typedef uint64_t mask;
static const mask dilate_2 = (mask)0x7FC0000FF80001FFLL ;
static const mask dilate_1 = (mask)0x01C0E070381C0E07LL ;
static const mask dilate_0 = (mask)0x9249249249249249LL ;
From my poor c++ understanding, I think that the hex values are 64bit
integer values (they have LL in the ending).
Now in Fortran my problem first was, that the definition with
integer(kind=8), parameter ...
did not work, as Vladimir said, because
integer(kind=8), ...
might be no 64bit integer.
Than I tested Alexanders solution, which works for the first and the
second (dilate_2, dilate_1) constant.
Also Vladimirs solution works for these two.
Now for dilate_0 none of these solutions work. I would suppose that Vladimirs solution will cast 0x9249249249249249LL (what is actually
a greater integer than allowed in INT64) into a INT64
if I do:
integer(INT64), parameter :: dilate_0 = int(Z'9249249249249249', &
kind=kind(dilate_0)
But this also don't work and gfortran give me an error:
Error: Arithmetic overflow converting INTEGER(16) to INTEGER(8) at (1).
So my actual question is how to implement this constant in Fortran?
As Vladimir posted in his comment integer(kind=8) is not portable (and not of kind 16 as the compiler complains).
As a remedy I suggest to use the intrinsic module ISO_Fortran_env (Fortran 2003) which has many predefined constants for the compiler used. Using INT64 from this module solves your problem and results in portable code:
program test
use,intrinsic :: ISO_Fortran_env, only: INT64
integer(INT64), parameter :: mask = Z'7FC0000FF80001FF'
print *,mask
end program
Z'9249249249249249' is not representable as a an INT64 (which is equivalent to an INTEGER(kind=8) in gfortran) because
BOZ constants are signed numbers (the same as every other integer constant in Fortran)
This number is larger than 2**63-1, the largest representable number for an INT64
Gfortran therefore selects the smallest integer type which fits, which is INTEGER(KIND=16).
We then have parameter staement where an INTEGER(KIND=8) parameter should be assigned a value outside its range. This is what the compiler complains about. It would complain the same way about
INTEGER(KIND=4), PARAMETER :: N = 37094947285
If you want to get around this, you can use the -fno-range-check option to gfortran. Information about -fno-range-check is already included in the gfortran error message (the part you didn't show).
I would do this to stay standard conforming
integer(whatever), parameter :: mask = int(Z'7FC0000FF80001FF', &
kind=kind(mask))
where whatever is some kind constant of the required value. It could be int64.
The above will not work if the constant corresponds to a negative number. One then has to make a trick like:
integer(int32), parameter :: mask = transfer(int(Z'A0000000',int64),1_int32)
or
integer(int32), parameter :: mask = transfer(Z'A0000000',1_int32)
but I am not sure whether the last one is strictly standard conforming.