You signed in with another tab or window. Reload to refresh your session.You signed out in another tab or window. Reload to refresh your session.You switched accounts on another tab or window. Reload to refresh your session.Dismiss alert
We also need to discuss whether we want to be more rigorous and try to support all available kind parameters from iso_fortran_env or generate the kinds using selected_real_kind.
I think it would be nice to support also the x86 extended 80-bit precision available (real(kind=10)) in generic procedures. There is at-least one place where I could use this now that I'm aware of it.
Personally, I'm kind of against the real32, real64, and real128 for reasons explained by Dr Fortran in "It it takes all KINDS", and believe it would be better if stdlib based it's constants on selected_**_kind.
Maybe we can list the required precision type as some options in common.fypp, and use the existing precision (4, 8, 16) by default.
Requires stdlib to use fypp to support(generate) more than 3 precisions, which is a big burden for stdlib before there is no generics and dimension(..) (I believe stdlib_stats will depends on dimension(..)),
Personally, I'm kind of against the real32, real64, and real128 for reasons explained by Dr Fortran in "It it takes all KINDS", and believe it would be better if stdlib based it's constants on selected_**_kind.
While I may have written otherwise in the past, I would be now in favor of using selected_*_kind in stdlib_kind.f90.
Since all modules use stdlib_kinds, changing the definitions of the different kinds should be automically propagated to the whole stdlib.
Adding a new kind (e.g. real(kind=10)) should be quite easy: only stdlib_kinds and common.fypp must be modified.
I just read this interesting thread and comment in Discourse.
@aradi proposed also a possible solution here, which I think could be doable in stdlib: a small Fortran program would generate stdlib_kinds.f90 that depends on hardware/sofware and a common.fypp with the different _KINDS fypp variables.
We already have a check for real128 in the CMake build files, but this option is not used. I can give it a try and expand this a bit. If I'm allowed to ignore the manual Makefile build I will send a patch for the CMake / fypp setup today or tomorrow.
Indeed, this check is not used anymore.
I just saw that NAG compilers provide `real16` in `iso_fortran_env`. Such a
strategy as proposed could support this too.
I guess that supporting first CMake / fypp is fine for a first test.
Le jeu. 19 août 2021 à 11:18, Sebastian Ehlert ***@***.***> a
écrit :
I didn't read the old threads again and I'm not sure that stdlib_kinds was meant for the end-user, but to be used internally by other stdlib modules. It's possible that that's why the spec was omitted. Is there a good end-use case for stdlib_kinds when there's already the constants from iso_fortran_env and selected_real_kind?
My personal understanding was that it is also for the end user. In all of my personal Fortran projects, I always have a precision module which offers the sp, dp, and wp constants. With stdlib_kinds I thought we ultimately save ourselves from having to rewrite this module again and again, and also settle on common variable names.
But now that you mention the alternative of keeping it for stdlib internal use only, I find it kind of appealing. One of the python zens is "There should be one-- and preferably only one --obvious way to do it". Fortran already has the mechanism with kind and selected_real_kind. On the other hand some of the statistics routine currently return a real(dp) result, meaning dp should probably be available to the end user; or, we must rewrite the documentation to state the return value is kind(1.0d0).
I don't think it make a difference if stdlib_kinds is meant for the end-user, or not.
As mentioned by @kargl 's comment in Discourse I think it would be good that all kinds provided by iso_fortran_env should be at least supported by stdlib. However, the numbers might differ across compiler/os (or even within compilers depending on the chosen options).
If the docs specify how are the different kinds defined in stdlib, then it does not matter if it is available to the user, or not IMO.
@jvdp1 I may not have been clear, I was only commenting on why there may not have been user-facing docs for this module. Of course, users can use the module either way. And of course, it doesn't hurt to write a user-doc, even if meant only for internal use.
@jvdp1 I may not have been clear, I was only commenting on why there may not have been user-facing docs for this module. Of course, users can use the module either way. And of course, it doesn't hurt to write a user-doc, even if meant only for internal use.
Sorry @milancurcic , I misunderstood your comment. IMO there was no specs, because it was one of the first modules developed. The first specs appeared with the function mean if I remember well ;)
Adding more kind parameters or making one of existing optional adds a problem with the tests. Since the test use the kind parameters explicitly, while the routines in stdlib get generated we have to guard all tests that use kind parameters, which could be optional.
I added fypp support to the CMake macro and realized that this would also be required in the manual Makefile logic. A bit more complicated. It would be nice if we could skip tests, but the current setup of the testsuite doesn't allow this, because the different precision tests are embedded in a single tester and there we can't just use stop 77, because it eliminates the complete test.
Documentation is still something I can do for the current implementation. But to have more kind parameters I think we need a bit of restructuring, which I would submit in separate incremental patches.
Adding more kind parameters or making one of existing optional adds a problem with the tests. Since the test use the kind parameters explicitly, while the routines in stdlib get generated we have to guard all tests that use kind parameters, which could be optional.
fypp could be used for the tests too (at least some of them). I was planning to modify some the stats tests for using fypp. I think that sorting tests could used fypp too
What about the following strategy:
- If a particular kind is not supported, turn it into a default kind
- In that case, clearly report that this had t obe done
It may generate redundant tests, but if implementing conditions on the test
programs is too hard, then it might be a workable alternative.
Op zo 22 aug. 2021 om 17:26 schreef Jeremie Vandenplas <
***@***.***>:
If all kinds supported by compiler need to be considered, the following tiny fortran program may generate all the real kinds supported? Integer kinds can be obtained similarly :)
program main
implicit noneinteger:: i,k,nk,iu
integer:: all_kinds(0:50)
10format(A, *('"',I0,'"',:,', '))
open(newunit=iu, file="compiler_kinds.fypp", status="replace", action="write")
all_kinds =-1; i=0; nk=0do
i = i+1
k =selected_real_kind(i)
if (k>0.and. k/=all_kinds(nk)) then
nk = nk+1
all_kinds(nk) = k
elseif (k<0) then
exit
end ifend dowrite(iu, 10, advance="no") "#:set REAL_KINDS = [", all_kinds(1:nk)
write(iu, "(A)") "]"close(iu)
end program
Not necessarily, there could be kinds that are not distinguished by the
precision. In a distant past I have used a Convex computer that had two
different single-precision reals. The difference was in the representation
of the exponent and the advantage of the native version was that it was a
bit faster for the computer to work with. (Well, this was before Fortran 90
was wide-spread). Such a kind is not distinguished via this program. You
could use the ISO_FORTRAN_ENV moduke to get a list of the supported kinds.
Op ma 23 aug. 2021 om 11:06 schreef Cheng ***@***.***>:
Activity
awvwgk commentedon Aug 18, 2021
We also need to discuss whether we want to be more rigorous and try to support all available kind parameters from
iso_fortran_env
or generate the kinds usingselected_real_kind
.ivan-pi commentedon Aug 18, 2021
Previous discussions on this topic include
sp
,dp
,qp
kinds constants #85 (discussion on naming convention)I think it would be nice to support also the x86 extended 80-bit precision available (
real(kind=10)
) in generic procedures. There is at-least one place where I could use this now that I'm aware of it.Personally, I'm kind of against the
real32
,real64
, andreal128
for reasons explained by Dr Fortran in "It it takes all KINDS", and believe it would be better ifstdlib
based it's constants onselected_**_kind
.zoziha commentedon Aug 19, 2021
Maybe we can list the required precision type as some options in
common.fypp
, and use the existing precision (4, 8, 16) by default.Requires
stdlib
to usefypp
to support(generate
) more than 3 precisions, which is a big burden forstdlib
before there is nogenerics
anddimension(..)
(I believestdlib_stats
will depends ondimension(..)
),jvdp1 commentedon Aug 19, 2021
While I may have written otherwise in the past, I would be now in favor of using
selected_*_kind
instdlib_kind.f90
.Since all modules use
stdlib_kinds
, changing the definitions of the different kinds should be automically propagated to the whole stdlib.Adding a new kind (e.g.
real(kind=10)
) should be quite easy: onlystdlib_kinds
andcommon.fypp
must be modified.jvdp1 commentedon Aug 19, 2021
I just read this interesting thread and comment in Discourse.
@aradi proposed also a possible solution here, which I think could be doable in
stdlib
: a small Fortran program would generatestdlib_kinds.f90
that depends on hardware/sofware and acommon.fypp
with the different_KINDS
fypp variables.awvwgk commentedon Aug 19, 2021
We already have a check for
real128
in the CMake build files, but this option is not used. I can give it a try and expand this a bit. If I'm allowed to ignore the manual Makefile build I will send a patch for the CMake / fypp setup today or tomorrow.jvdp1 commentedon Aug 19, 2021
milancurcic commentedon Aug 19, 2021
I didn't read the old threads again and I'm not sure that
stdlib_kinds
was meant for the end-user, but to be used internally by other stdlib modules. It's possible that that's why the spec was omitted. Is there a good end-use case forstdlib_kinds
when there's already the constants fromiso_fortran_env
andselected_real_kind
?ivan-pi commentedon Aug 19, 2021
My personal understanding was that it is also for the end user. In all of my personal Fortran projects, I always have a
precision
module which offers thesp
,dp
, andwp
constants. Withstdlib_kinds
I thought we ultimately save ourselves from having to rewrite this module again and again, and also settle on common variable names.But now that you mention the alternative of keeping it for
stdlib
internal use only, I find it kind of appealing. One of the python zens is "There should be one-- and preferably only one --obvious way to do it". Fortran already has the mechanism withkind
andselected_real_kind
. On the other hand some of the statistics routine currently return areal(dp)
result, meaningdp
should probably be available to the end user; or, we must rewrite the documentation to state the return value iskind(1.0d0)
.jvdp1 commentedon Aug 19, 2021
I don't think it make a difference if
stdlib_kinds
is meant for the end-user, or not.As mentioned by @kargl 's comment in Discourse I think it would be good that all kinds provided by
iso_fortran_env
should be at least supported bystdlib
. However, the numbers might differ across compiler/os (or even within compilers depending on the chosen options).If the docs specify how are the different kinds defined in
stdlib
, then it does not matter if it is available to the user, or not IMO.milancurcic commentedon Aug 19, 2021
@jvdp1 I may not have been clear, I was only commenting on why there may not have been user-facing docs for this module. Of course, users can use the module either way. And of course, it doesn't hurt to write a user-doc, even if meant only for internal use.
jvdp1 commentedon Aug 19, 2021
Sorry @milancurcic , I misunderstood your comment. IMO there was no specs, because it was one of the first modules developed. The first specs appeared with the function
mean
if I remember well ;)awvwgk commentedon Aug 21, 2021
Adding more kind parameters or making one of existing optional adds a problem with the tests. Since the test use the kind parameters explicitly, while the routines in stdlib get generated we have to guard all tests that use kind parameters, which could be optional.
I added fypp support to the CMake macro and realized that this would also be required in the manual Makefile logic. A bit more complicated. It would be nice if we could skip tests, but the current setup of the testsuite doesn't allow this, because the different precision tests are embedded in a single tester and there we can't just use
stop 77
, because it eliminates the complete test.Documentation is still something I can do for the current implementation. But to have more kind parameters I think we need a bit of restructuring, which I would submit in separate incremental patches.
jvdp1 commentedon Aug 22, 2021
fypp
could be used for the tests too (at least some of them). I was planning to modify some the stats tests for using fypp. I think that sorting tests could used fypp tooarjenmarkus commentedon Aug 23, 2021
qin-tain commentedon Aug 23, 2021
If all kinds supported by compiler need to be considered, the following tiny fortran program may generate all the real kinds supported? Integer kinds can be obtained similarly :)
arjenmarkus commentedon Aug 23, 2021
nshaffer commentedon Sep 25, 2021
Why can't we use the arrays defined in
iso_fortran_env
? Is there a reason we need to dig further than that?This can be extended trivially with
integer_kinds
,logical_kinds
,character_kinds
. Have I missed some non-obvious requirement?