Discussion:
SELECTED_REAL_KIND skips valid KIND on Free BSD 9.3
(too old to reply)
Scot
2016-05-11 21:36:00 UTC
Permalink
gfortran4.8 on FreeBSD 9.3 i386 seems to be skipping KIND=10 for
precision 16-18. I've check that C_LONG_DOUBLE is KIND=10 which is 12
bytes. But when the program below is compiled and run, it does not
detect that KIND=10 is valid for ik 16-18. What am I missing? I've not
seen this issue on any other system.
I would expect the output below, but on FreeBSD it skips 10 and goes to
16 instead:
C_LONG_DOUBLE: KIND, SIZEOF 10 12
precision 2 kind 4
precision 3 kind 4
precision 4 kind 4
precision 5 kind 4
precision 6 kind 4
precision 7 kind 8
precision 8 kind 8
precision 9 kind 8
precision 10 kind 8
precision 11 kind 8
precision 12 kind 8
precision 13 kind 8
precision 14 kind 8
precision 15 kind 8
precision 16 kind 10
precision 17 kind 10
precision 18 kind 10
precision 19 kind 16
precision 20 kind 16


PROGRAM main
USE ISO_C_BINDING
IMPLICIT NONE
INTEGER :: ik, k
REAL(C_LONG_DOUBLE) :: cld
PRINT*,"C_LONG_DOUBLE: KIND, SIZEOF",C_LONG_DOUBLE, sizeof(cld)
DO ik=2,20
k = SELECTED_REAL_KIND(ik)
print*,"precision",ik,"kind",k
IF (k .LE. 0) EXIT
ENDDO
END
jfh
2016-05-11 22:23:45 UTC
Permalink
Post by Scot
gfortran4.8 on FreeBSD 9.3 i386 seems to be skipping KIND=10 for
precision 16-18. I've check that C_LONG_DOUBLE is KIND=10 which is 12
bytes. But when the program below is compiled and run, it does not
detect that KIND=10 is valid for ik 16-18. What am I missing? I've not
seen this issue on any other system.
I would expect the output below, but on FreeBSD it skips 10 and goes to
C_LONG_DOUBLE: KIND, SIZEOF 10 12
precision 2 kind 4
precision 3 kind 4
precision 4 kind 4
precision 5 kind 4
precision 6 kind 4
precision 7 kind 8
precision 8 kind 8
precision 9 kind 8
precision 10 kind 8
precision 11 kind 8
precision 12 kind 8
precision 13 kind 8
precision 14 kind 8
precision 15 kind 8
precision 16 kind 10
precision 17 kind 10
precision 18 kind 10
precision 19 kind 16
precision 20 kind 16
PROGRAM main
USE ISO_C_BINDING
IMPLICIT NONE
INTEGER :: ik, k
REAL(C_LONG_DOUBLE) :: cld
PRINT*,"C_LONG_DOUBLE: KIND, SIZEOF",C_LONG_DOUBLE, sizeof(cld)
DO ik=2,20
k = SELECTED_REAL_KIND(ik)
print*,"precision",ik,"kind",k
IF (k .LE. 0) EXIT
ENDDO
END
On our x86_64 system gfortran 4.4.7 and 6.0.0 both gave the output the OP expected, with one exception: it began with
C_LONG_DOUBLE: KIND, SIZEOF 10 16
(16 instead of 12).
h***@gmail.com
2016-05-11 23:50:26 UTC
Permalink
Post by Scot
gfortran4.8 on FreeBSD 9.3 i386 seems to be skipping KIND=10 for
precision 16-18. I've check that C_LONG_DOUBLE is KIND=10 which is 12
bytes. But when the program below is compiled and run, it does not
detect that KIND=10 is valid for ik 16-18. What am I missing? I've not
seen this issue on any other system.
I would expect the output below, but on FreeBSD it skips 10 and goes to
(snip of output not showing what the OP wants to show)

I suspect that there isn't a rule requiring SELECTED_xxx_KIND to support all kinds
that the hardware supports.
Post by Scot
PROGRAM main
USE ISO_C_BINDING
IMPLICIT NONE
INTEGER :: ik, k
REAL(C_LONG_DOUBLE) :: cld
PRINT*,"C_LONG_DOUBLE: KIND, SIZEOF",C_LONG_DOUBLE, sizeof(cld)
DO ik=2,20
k = SELECTED_REAL_KIND(ik)
print*,"precision",ik,"kind",k
IF (k .LE. 0) EXIT
ENDDO
END
-- glen
Richard Maine
2016-05-12 00:29:49 UTC
Permalink
Post by h***@gmail.com
I suspect that there isn't a rule requiring SELECTED_xxx_KIND to support
all kinds that the hardware supports.
Hardware, no. Of course not. The Fortran standard doesn't really have a
concept of hardware and the kinds supported don't have to have anything
to do with hardware. Software floating point implementations have
actually been pretty common. But there are internal consistency
requirements on the "processor" (which I'll refer to as the compiler for
simplicity).

If there just isn't kind=10 at all, then all is fine. But in that case
the compiler is required to have the capability of diagnosing the use of
kind=10. See f2003 1.5(4). That's one of the few sorts of things that
compilers are required to be able to diagnose. Granted, the diagnosis
can be optional as long as the capability is there. So it would be valid
for there to be a switch saying to go ahead and accept a kind=10 even
though it is not a "supported" kind. That would be a bit quirky, but ok.
Similar issues have come up before as hacks around a compiler not
implementing complex for all real kinds, as required by the standard.
Just declare that the kind in question (typically a quad precision) is
not a "supported" real kind. That one has happened. There does have to
be an option to diagnose it, though or the compiler is in violation.
(And I believe the compiler that I recall doing this was in violation
because of that).

If it is claimed that no diagnosis is needed because kind=10 is a
supported real kind, then yes, selected_real_kind has to deal with it.
This isn't exactly subtle if one actually reads the definition of
selected_real_kind instead of just guessing what it might say. From that
definition in f2003

"If more than one kind type parameter value meets the criteria, the
value returned is the one with the smallest decimal precision,
unless [condition that doesn't apply here]."

So no, the compiler isn't allowed to just decide that it doesn't feel
like returning kind=10. If that kind is supported then the compiler is
not allowed to return the value for some higher precision.

In summary, none of this has anything at all to do with hardware. What
it does have to do with is internal consistency on whether the kind
counts as one "supported" by the "processor". If it is supported, then
things like selected_real_kind have to work with it. If it is not
supported, then there has to be a capability to diagnose attempts to use
it.
--
Richard Maine
email: last name at domain . net
dimnain: summer-triangle
h***@gmail.com
2016-05-12 01:11:29 UTC
Permalink
On Wednesday, May 11, 2016 at 5:29:52 PM UTC-7, Richard Maine wrote:

(snip, I wrote)
Post by Richard Maine
Post by h***@gmail.com
I suspect that there isn't a rule requiring SELECTED_xxx_KIND to support
all kinds that the hardware supports.
Hardware, no. Of course not. The Fortran standard doesn't really have a
concept of hardware and the kinds supported don't have to have anything
to do with hardware. Software floating point implementations have
actually been pretty common. But there are internal consistency
requirements on the "processor" (which I'll refer to as the compiler for
simplicity).
If there just isn't kind=10 at all, then all is fine. But in that case
the compiler is required to have the capability of diagnosing the use of
kind=10. See f2003 1.5(4). That's one of the few sorts of things that
compilers are required to be able to diagnose. Granted, the diagnosis
can be optional as long as the capability is there. So it would be valid
for there to be a switch saying to go ahead and accept a kind=10 even
though it is not a "supported" kind. That would be a bit quirky, but ok.
Similar issues have come up before as hacks around a compiler not
implementing complex for all real kinds, as required by the standard.
Just declare that the kind in question (typically a quad precision) is
not a "supported" real kind. That one has happened. There does have to
be an option to diagnose it, though or the compiler is in violation.
(And I believe the compiler that I recall doing this was in violation
because of that).
OK, but how about a system that supported arithmetic operators for
KIND=10, but didn't have intrinsic functions for that KIND.

In this case, the ability to work with a C compiler that supports it would
make it useful, or maybe require it, for C interoperability to work.

If one wanted, one could call the C functions.
Post by Richard Maine
If it is claimed that no diagnosis is needed because kind=10 is a
supported real kind, then yes, selected_real_kind has to deal with it.
This isn't exactly subtle if one actually reads the definition of
selected_real_kind instead of just guessing what it might say. From that
definition in f2003
"If more than one kind type parameter value meets the criteria, the
value returned is the one with the smallest decimal precision,
unless [condition that doesn't apply here]."
So no, the compiler isn't allowed to just decide that it doesn't feel
like returning kind=10. If that kind is supported then the compiler is
not allowed to return the value for some higher precision.
So, as above, one might need the ability to allocate such, pass them to and
from C, but not otherwise use them in Fortran. That would seem to me to
be "not supported" in the Fortran sense.

Though from your comments, it seems that a compiler should
give a warning in that case.
Post by Richard Maine
In summary, none of this has anything at all to do with hardware. What
it does have to do with is internal consistency on whether the kind
counts as one "supported" by the "processor". If it is supported, then
things like selected_real_kind have to work with it. If it is not
supported, then there has to be a capability to diagnose attempts to use
it.
-- glen
Richard Maine
2016-05-12 01:41:55 UTC
Permalink
[about incompletely supported kinds]
Post by h***@gmail.com
Post by Richard Maine
But there are internal consistency
requirements on the "processor"
OK, but how about a system that supported arithmetic operators for
KIND=10, but didn't have intrinsic functions for that KIND.
...
Post by h***@gmail.com
So, as above, one might need the ability to allocate such, pass them to and
from C, but not otherwise use them in Fortran. That would seem to me to
be "not supported" in the Fortran sense.
Though from your comments, it seems that a compiler should
give a warning in that case.
Yep. I'd agree with that analysis, at least as far as it goes. But it is
tricky to get such "partial support" 100% consistent. For example, the
named constants for C kinds in the C interop stuff have to either be
supported kinds or negative. Simillarly with things like
selected_real_kind; any non-negative value returned from it has to be
for a supported kind.

So while in theory you could have an incompletely implemented kind,
making one that still conformed to the standard would require quite a
bit of care. The ability to give a diagnostic is just one piece. I am
not aware of it ever actually having been done in full conformance to
the standard. As I previously noted, there was a compiler that tried to
claim that quad precision real was an extension and thus they could get
by without a corresponding complex. But that claim appeared to be more
of an after-the-fact attempt at rationalization than an actual part of
the design specs. It didn't do the things that would be required to make
it count as a conforming extension, with the result that it could break
code that was completely standard conforming. I forget all the details
of how it failed to conform, but having selected_real_kind return a
positive kind value that could not be used for complex would be one
likely ssuch failure.
--
Richard Maine
email: last name at domain . net
dimnain: summer-triangle
steve kargl
2016-05-12 02:50:47 UTC
Permalink
Post by Richard Maine
Post by h***@gmail.com
I suspect that there isn't a rule requiring SELECTED_xxx_KIND to support
all kinds that the hardware supports.
If it is claimed that no diagnosis is needed because kind=10 is a
supported real kind, then yes, selected_real_kind has to deal with it.
This isn't exactly subtle if one actually reads the definition of
selected_real_kind instead of just guessing what it might say. From that
definition in f2003
"If more than one kind type parameter value meets the criteria, the
value returned is the one with the smallest decimal precision,
unless [condition that doesn't apply here]."
So no, the compiler isn't allowed to just decide that it doesn't feel
like returning kind=10. If that kind is supported then the compiler is
not allowed to return the value for some higher precision.
We have a winner! Freebsd on i386 has two kinds with the
number of digits.
--
steve
Richard Maine
2016-05-12 03:39:18 UTC
Permalink
Post by steve kargl
Post by Richard Maine
Post by h***@gmail.com
I suspect that there isn't a rule requiring SELECTED_xxx_KIND to support
all kinds that the hardware supports.
If it is claimed that no diagnosis is needed because kind=10 is a
supported real kind, then yes, selected_real_kind has to deal with it.
This isn't exactly subtle if one actually reads the definition of
selected_real_kind instead of just guessing what it might say. From that
definition in f2003
"If more than one kind type parameter value meets the criteria, the
value returned is the one with the smallest decimal precision,
unless [condition that doesn't apply here]."
So no, the compiler isn't allowed to just decide that it doesn't feel
like returning kind=10. If that kind is supported then the compiler is
not allowed to return the value for some higher precision.
We have a winner! Freebsd on i386 has two kinds with the
number of digits.
Hmm. Ok. I didn't know that. I guess the "unless" bit does apply then.
Does it then meet that part of the spec?

"...unless there are several such values, in which case the smallest
of those kind values is returned."

No, I haven't looked up the details of the freebsd implementation, but
if I understand correctly (which I might not), it tort of sounds like
kind=10 ought to be returned instead of 16.
--
Richard Maine
email: last name at domain . net
dimnain: summer-triangle
steve kargl
2016-05-12 10:47:29 UTC
Permalink
Post by Richard Maine
Post by steve kargl
Post by Richard Maine
Post by h***@gmail.com
I suspect that there isn't a rule requiring SELECTED_xxx_KIND to support
all kinds that the hardware supports.
If it is claimed that no diagnosis is needed because kind=10 is a
supported real kind, then yes, selected_real_kind has to deal with it.
This isn't exactly subtle if one actually reads the definition of
selected_real_kind instead of just guessing what it might say. From that
definition in f2003
"If more than one kind type parameter value meets the criteria, the
value returned is the one with the smallest decimal precision,
unless [condition that doesn't apply here]."
So no, the compiler isn't allowed to just decide that it doesn't feel
like returning kind=10. If that kind is supported then the compiler is
not allowed to return the value for some higher precision.
We have a winner! Freebsd on i386 has two kinds with the
number of digits.
Hmm. Ok. I didn't know that. I guess the "unless" bit does apply then.
Does it then meet that part of the spec?
"...unless there are several such values, in which case the smallest
of those kind values is returned."
No, I haven't looked up the details of the freebsd implementation, but
if I understand correctly (which I might not), it tort of sounds like
kind=10 ought to be returned instead of 16.
I won't be able to post details until Saturday as I'm sitting in a hotel
in front of a Win 7 system. OP needs to look at what the numeric
inquiry intrinsics return for digits, precision, maxexponent, tiny, and
huge. There's a reaason why selected_real_kind takes more than
one argument.
--
steve
steve kargl
2016-05-12 02:47:25 UTC
Permalink
Post by Scot
gfortran4.8 on FreeBSD 9.3 i386 seems to be skipping KIND=10 for
precision 16-18. I've check that C_LONG_DOUBLE is KIND=10 which is 12
bytes. But when the program below is compiled and run, it does not
detect that KIND=10 is valid for ik 16-18. What am I missing? I've not
seen this issue on any other system.
I would expect the output below, but on FreeBSD it skips 10 and goes to
C_LONG_DOUBLE: KIND, SIZEOF 10 12
precision 2 kind 4
precision 3 kind 4
precision 4 kind 4
precision 5 kind 4
precision 6 kind 4
precision 7 kind 8
precision 8 kind 8
precision 9 kind 8
precision 10 kind 8
precision 11 kind 8
precision 12 kind 8
precision 13 kind 8
precision 14 kind 8
precision 15 kind 8
precision 16 kind 10
precision 17 kind 10
precision 18 kind 10
precision 19 kind 16
precision 20 kind 16
PROGRAM main
USE ISO_C_BINDING
IMPLICIT NONE
INTEGER :: ik, k
REAL(C_LONG_DOUBLE) :: cld
PRINT*,"C_LONG_DOUBLE: KIND, SIZEOF",C_LONG_DOUBLE, sizeof(cld)
DO ik=2,20
k = SELECTED_REAL_KIND(ik)
print*,"precision",ik,"kind",k
IF (k .LE. 0) EXIT
ENDDO
END
The reason is simply, but you obviously don't understanding the floating environment
for FreeBSD on i386 class hardware. Try exploring the environment with

program foo
real(4) x04
real(8) x08
real(10) x10
real(16) x16
print *, digits(x04), digits(x08), digits(x10), digits(x16)
print *, precision (x04), precision(x08), precision(x10), precision(x16)
print *, minexponent......
print *, maxexponent.....
print *, tiny...
print *, huge ....
end program
--
steve
Scot
2016-05-12 14:56:58 UTC
Permalink
Post by steve kargl
The reason is simply, but you obviously don't understanding the floating environment
for FreeBSD on i386 class hardware. Try exploring the environment with
program foo
real(4) x04
real(8) x08
real(10) x10
real(16) x16
print *, digits(x04), digits(x08), digits(x10), digits(x16)
print *, precision (x04), precision(x08), precision(x10), precision(x16)
print *, minexponent......
print *, maxexponent.....
print *, tiny...
print *, huge ....
end program
digits: 24 53 53 113
precision 6 15 15 33
minexponent -125 -1021 -16381 -16381
maxexponent 128 1024 16384 16384
tiny 1.17549435E-38 2.22507385850720138E-308
3.36210314311209350626E-4932
3.36210314311209350626267781732175260E-4932
huge 3.40282347E+38 1.79769313486231571E+308
1.18973149535723163300E+4932
1.18973149535723176508575932662800702E+4932

For:
selected_real_kind(15,1:307) = 8
selected_real_kind(15,308:4931) = 10, -2 for R>4931
selected_real_kind(16,1:4931) = 16, -2 for R>4931

So since both KIND=8 and KIND=10 have the same precision, it choses
the smaller exponent range KIND=8 if the exponent range is not given.
I'm assuming that is the standard convention.
h***@gmail.com
2016-05-12 23:48:25 UTC
Permalink
This post might be inappropriate. Click to display it.
steve kargl
2016-05-13 01:21:16 UTC
Permalink
Post by h***@gmail.com
(snip)
Post by Scot
digits: 24 53 53 113
precision 6 15 15 33
minexponent -125 -1021 -16381 -16381
maxexponent 128 1024 16384 16384
tiny 1.17549435E-38 2.22507385850720138E-308
3.36210314311209350626E-4932
3.36210314311209350626267781732175260E-4932
huge 3.40282347E+38 1.79769313486231571E+308
1.18973149535723163300E+4932
1.18973149535723176508575932662800702E+4932
Since the beginning of the 8087 usage, it has never been obvious who
should set the control register bits.
I believe that there have even been systems that didn't give them specific
values before starting a program, such that they kept the values from some
previous program.
Many systems have a call that will set or clear some of the bits, as
appropriate for the program, though actually doing it has been rare.
Two bits set the precision used for some (not all) operations.
It looks like FreeBSD is setting the bits for 53 bit precision.
That tries to avoids the problem of different results between register values and
values stored and reloaded from memory. I don't know that x87 defines the result
to be the same, and it only applies to some operations. I forget now which operations
follow the bits, and which ones don't.
https://svnweb.freebsd.org/base/head/sys/x86/include/fpu.h?revision=274817&view=markup
--
steve
h***@gmail.com
2016-05-13 02:06:24 UTC
Permalink
On Thursday, May 12, 2016 at 6:24:51 PM UTC-7, steve kargl wrote:

(snip)
Post by steve kargl
https://svnweb.freebsd.org/base/head/sys/x86/include/fpu.h?revision=274817&view=markup
After a lot of C declarations, says:

* FreeBSD/i386 uses 53 bit precision for things like fadd/fsub/fsqrt etc
* because of the difference between memory and fpu register stack arguments.
* If its using an intermediate fpu register, it has 80/64 bits to work
* with. If it uses memory, it has 64/53 bits to work with. However,
* gcc is aware of this and goes to a fair bit of trouble to make the
* best use of it.

As above, I don't actually know that the values you get with 53 bit mode are the same
as storing and reloading as a C double, but interesting anyway.

-- glen
James Van Buskirk
2016-05-13 16:44:24 UTC
Permalink
Post by steve kargl
The reason is simply, but you obviously don't understanding the floating environment
for FreeBSD on i386 class hardware. Try exploring the environment with
program foo
real(4) x04
real(8) x08
real(10) x10
real(16) x16
print *, digits(x04), digits(x08), digits(x10), digits(x16)
print *, precision (x04), precision(x08), precision(x10),
precision(x16)
print *, minexponent......
print *, maxexponent.....
print *, tiny...
print *, huge ....
end program
I prefer to automate this process a little more with

D:\gfortran\clf\sound>type reals.f90
program reals
use ISO_FORTRAN_ENV
implicit none
integer i
write(*,'(a)') 'kind precision range'
write(*,'(i4,i10,i6)') [(kind(real(0,REAL_KINDS(i))), &
precision(real(0,REAL_KINDS(i))), &
range(real(0,REAL_KINDS(i))),i=1,size(REAL_KINDS))]
end program reals

D:\gfortran\clf\sound>gfortran reals.f90 -oreals
reals.f90:6:40:

write(*,'(i4,i10,i6)') [(kind(real(0,REAL_KINDS(i))), &
1
Error: Invalid kind for REAL at (1)
reals.f90:7:23:

precision(real(0,REAL_KINDS(i))), &
1
Error: Invalid kind for REAL at (1)
reals.f90:8:19:

range(real(0,REAL_KINDS(i))),i=1,size(REAL_KINDS))]
1
Error: Invalid kind for REAL at (1)

D:\gfortran\clf\sound>ifort reals.f90
Intel(R) Visual Fortran Compiler for applications running on IA-32, Version
16.0
.2.180 Build 20160204
Copyright (C) 1985-2016 Intel Corporation. All rights reserved.

reals.f90(6): error #6683: A kind type parameter must be a compile-time
constant
. [REAL_KINDS]
write(*,'(i4,i10,i6)') [(kind(real(0,REAL_KINDS(i))), &
----------------------------------------^
reals.f90(7): error #6683: A kind type parameter must be a compile-time
constant
. [REAL_KINDS]
precision(real(0,REAL_KINDS(i))), &
-----------------------^
reals.f90(8): error #6683: A kind type parameter must be a compile-time
constant
. [REAL_KINDS]
range(real(0,REAL_KINDS(i))),i=1,size(REAL_KINDS))]
-------------------^
compilation aborted for reals.f90 (code 1)

Jeez, I was hoping for an ICE rather than an invalid error message :)
FortranFan
2016-05-13 23:07:36 UTC
Permalink
Post by James Van Buskirk
..
reals.f90(6): error #6683: A kind type parameter must be a compile-time
constant
. [REAL_KINDS]
write(*,'(i4,i10,i6)') [(kind(real(0,REAL_KINDS(i))), &
----------------------------------------^
reals.f90(7): error #6683: A kind type parameter must be a compile-time
constant
..
Jeez, I was hoping for an ICE rather than an invalid error message :)
So I take it your "mental" compiler thought REAL_KINDS(i) usage is indeed invalid but you didn't expect either of the two compilers to succeed in informing you as such?
James Van Buskirk
2016-05-14 03:52:30 UTC
Permalink
Post by FortranFan
Post by James Van Buskirk
..
reals.f90(6): error #6683: A kind type parameter must be a compile-time
constant
. [REAL_KINDS]
write(*,'(i4,i10,i6)') [(kind(real(0,REAL_KINDS(i))), &
----------------------------------------^
reals.f90(7): error #6683: A kind type parameter must be a compile-time
constant
..
Jeez, I was hoping for an ICE rather than an invalid error message :)
So I take it your "mental" compiler thought REAL_KINDS(i) usage is
indeed invalid but you didn't expect either of the two compilers to
succeed in informing you as such?
No, that kind of stuff is valid. In 10.007.pdf section 7.1.12 it says:

"A constant expression is an expression with limitations that make
it suitable for use as a kind type parameter, initializer, or named
constant. It is an expression in which each operation is intrinsic,
and each primary is

...

(11) an ac-do-variable within an array constructor where each scalar-
int-expr of the corresponding ac-implied-do-control is a constant
expression"

But it's tricky for the compiler to figure out that such a usage is vaild
because it kind of has to try to expand all ac-implied-dos just to be
able to supply a constant when needed and this could get unwieldy
if the ac-implied-do expanded to a lot of data and the ac-implied-do-
control was made up of constant expressions while in the normal
case the constantness of the ac-do-variable is not required.

Applying a second-string compiler, whether the specification
expression compiler or the constant expression compiler to a
difficult situation is a frequent ICE producer.

Ian Chivers
2016-05-12 16:44:34 UTC
Permalink
Here is a portable program and output
to look at 32, 64, 80 and 128 bit reals
in Fortran.

At this time only gfortran and Salford Fortran
offer support for the 80 bit real.

program ch0509
implicit none
! real arithmetic
!
! 32 and 64 bit reals are normally available.
! The IEEE format is as described below.
!
! 32 bit reals 8 bit exponent, 24 bit mantissa
! 64 bit reals 11 bit exponent, 53 bit mantissa
!
integer, parameter :: &
sp = selected_real_kind( 6, 37)
integer, parameter :: &
dp = selected_real_kind(15, 307)
! Comment the next line out when using with other compilers.
! Only gfortran and Salford Fortran support
! 10 bytes reals.
integer, parameter :: &
zp = selected_real_kind(15, 310)
integer, parameter :: &
qp = selected_real_kind(30, 291)
real (sp) :: rsp
real (dp) :: rdp
! comment out the following line
real (zp) :: r
! replace with
! real :: r
! to chose default real.
real (qp) :: rqp
print *, ' ====================='
print *, ' Real kind information'
print *, ' ====================='
print *, ' kind number'
print *, ' ', kind(r) , ' ', kind(rsp) , &
' ' , kind(rdp),' ', kind(rqp)
print *, ' digits details'
print *, ' ', digits(r) , ' ', digits(rsp), &
' ', digits(rdp),' ',digits(rqp)
print *, ' epsilon details'
print *, ' ',epsilon(r)
print *, ' ',epsilon(rsp)
print *, ' ',epsilon(rdp)
print *, ' ',epsilon(rqp)
print *, ' huge value'
print *, ' ',huge(r)
print *, ' ',huge(rsp)
print *, ' ',huge(rdp)
print *, ' ',huge(rqp)
print *, ' maxexponent value'
print *, ' ',maxexponent(r)
print *, ' ',maxexponent(rsp)
print *, ' ',maxexponent(rdp)
print *, ' ',maxexponent(rqp)
print *, ' minexponent value'
print *, ' ',minexponent(r)
print *, ' ',minexponent(rsp)
print *, ' ',minexponent(rdp)
print *, ' ',minexponent(rqp)
print *, ' precision details'
print *, ' ', precision(r) , &
' ', precision(rsp) , &
' ', precision(rdp) , &
' ', precision(rqp)
print *, ' radix details'
print *, ' ' , radix(r) , &
' ', radix(rsp) , &
' ', radix(rdp) , &
' ', radix(rqp)
print *, ' range details'
print *, ' ', range(r) , &
' ', range(rsp) , &
' ', range(rdp) , &
' ', range(rqp)
print *, ' tiny details'
print *, ' ',tiny(r)
print *, ' ',tiny(rsp)
print *, ' ',tiny(rdp)
print *, ' ',tiny(rqp)

end program ch0509

=====================
Real kind information
=====================
kind number
10 4 8 16
digits details
64 24 53 113
epsilon details
1.08420217248550443401E-0019
1.19209290E-07
2.2204460492503131E-016
1.92592994438723585305597794258492732E-0034
huge value
1.18973149535723176502E+4932
3.40282347E+38
1.7976931348623157E+308
1.18973149535723176508575932662800702E+4932
maxexponent value
16384
128
1024
16384
minexponent value
-16381
-125
-1021
-16381
precision details
18 6 15 33
radix details
2 2 2 2
range details
4931 37 307 4931
tiny details
3.36210314311209350626E-4932
1.17549435E-38
2.2250738585072014E-308
3.36210314311209350626267781732175260E-4932
Loading...