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
I have downloaded the sources from the fpm branch and tried to compile them "manually" (I mean without fpm). The objective is to put the sources in our industrial software, which has its own build system, and IFORT 21 is the compiler I have to use (and which is not the list of the tested compilers).
The compilation is mostly OK, except for a couple of files, for which I had to apply some quick (and dirty?) fixes... Here is the list:
2 modules in a single filelin_stdlib_blas_constants.f90
It contains lin_stdlib_blas_constants_sp and lin_stdlib_blas_constants_dp. Our dependency management assumes that a source file can contain only one module, with the exact same name as the file (without the .f90 suffix). I think it's a very common convention, and it would be nice to split this into two files.
Internal compiler error instdlib_error.f90
It happens here:
puresubroutineappendr(msg,a,prefix)
class(*),optional,intent(in) :: a(..)
character(len=*),intent(inout) :: msg
character,optional,intent(in) :: prefix
if (present(a)) then
select rank (v=>a)
rank (0) !!! line 383 !!
call append (msg,v,prefix)
rank (1)
call appendv(msg,v)
rank default
msg =trim(msg)//' <ERROR: INVALID RANK>'
end select
endifendsubroutine appendr
pure integer(ilp) function stdlib_ieeeck( ispec, zero, one )
!! IEEECK is called from the ILAENV to verify that Infinity and
!! possibly NaN arithmetic is safe (i.e. will not trap).
! -- lapack auxiliary routine --
! -- lapack is a software package provided by univ. of tennessee, --
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
! Scalar Arguments
integer(ilp), intent(in) :: ispec
real(sp), intent(in) :: one, zero
! =====================================================================
! Executable Statements
stdlib_ieeeck =1
! Test support for infinity values
if (.not.ieee_support_inf(one)) then
stdlib_ieeeck =0returnend if
! returnif we were only asked to check infinity arithmetic
if (ispec == 0) returnif (.not.ieee_support_nan(one)) then
stdlib_ieeeck =0returnend ifreturn
end function stdlib_ieeeck
stdlib/lin_stdlib_linalg_lapack_aux.F90(138): error #7137: Any procedure referenced in a PURE procedure, including one referenced via a defined operation or assignment, must have an explicit interface and be declared PURE. [IEEE_ARITHMETIC^FOR_IEEE_SUPPORT_INF]
if (.not.ieee_support_inf(one)) then
--------------------^
stdlib/lin_stdlib_linalg_lapack_aux.F90(146): error #7137: Any procedure referenced in a PURE procedure, including one referenced via a defined operation or assignment, must have an explicit interface and be declared PURE. [IEEE_ARITHMETIC^FOR_IEEE_SUPPORT_NAN]
if (.not.ieee_support_nan(one)) then
--------------------^
This one is weird... I ended up by simply returning the value $0$, but again I don't know what are the consequences:
```fortran
pure integer(ilp) function stdlib_ieeeck( ispec, zero, one )
integer(ilp), intent(in) :: ispec
real(sp), intent(in) :: one, zero
stdlib_ieeeck = 0
end function stdlib_ieeeck
Expected Behaviour
successful compilation ;)
Version of stdlib
0.7.0
Platform and Architecture
Debian 11
Additional Information
No response
The text was updated successfully, but these errors were encountered:
Description
I have downloaded the sources from the fpm branch and tried to compile them "manually" (I mean without fpm). The objective is to put the sources in our industrial software, which has its own build system, and IFORT 21 is the compiler I have to use (and which is not the list of the tested compilers).
The compilation is mostly OK, except for a couple of files, for which I had to apply some quick (and dirty?) fixes... Here is the list:
2 modules in a single file
lin_stdlib_blas_constants.f90
It contains
lin_stdlib_blas_constants_sp
andlin_stdlib_blas_constants_dp
. Our dependency management assumes that a source file can contain only one module, with the exact same name as the file (without the .f90 suffix). I think it's a very common convention, and it would be nice to split this into two files.Internal compiler error in
stdlib_error.f90
It happens here:
stdlib/lin_stdlib_error.f90(383): catastrophic error: **Internal compiler error: internal abort**
I had to rewrite it to make it compile, but obviously nothing will be done for
rank(a)==0
, and I don't know if it's a problem or not:Unrecognized functions in
stdlib_linalg_lapack_aux.F90
It happens here:
This one is weird... I ended up by simply returning the value$0$ , but again I don't know what are the consequences:
Expected Behaviour
successful compilation ;)
Version of stdlib
0.7.0
Platform and Architecture
Debian 11
Additional Information
No response
The text was updated successfully, but these errors were encountered: