Skip to content

Commit

Permalink
Merge branch 'intrinsics' of https://github.com/jalvesz/stdlib into i…
Browse files Browse the repository at this point in the history
…ntrinsics
  • Loading branch information
jalvesz committed Jan 17, 2025
2 parents 6e36b6f + cc232e1 commit 65175d7
Show file tree
Hide file tree
Showing 4 changed files with 4 additions and 11 deletions.
3 changes: 1 addition & 2 deletions .github/workflows/ci_windows.yml
Original file line number Diff line number Diff line change
Expand Up @@ -13,8 +13,7 @@ jobs:
fail-fast: false
matrix:
include: [
{ msystem: MINGW64, arch: x86_64 },
{ msystem: MINGW32, arch: i686 }
{ msystem: MINGW64, arch: x86_64 }
]
defaults:
run:
Expand Down
4 changes: 2 additions & 2 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -90,15 +90,15 @@ Name | Version | Platform | Architecture
GCC Fortran | 10, 11, 12, 13 | Ubuntu 22.04.2 LTS | x86_64
GCC Fortran | 10, 11, 12, 13 | macOS 12.6.3 (21G419) | x86_64
GCC Fortran (MSYS) | 13 | Windows Server 2022 (10.0.20348 Build 1547) | x86_64
GCC Fortran (MinGW) | 13 | Windows Server 2022 (10.0.20348 Build 1547) | x86_64, i686
GCC Fortran (MinGW) | 13 | Windows Server 2022 (10.0.20348 Build 1547) | x86_64
Intel oneAPI LLVM | 2024.0 | Ubuntu 22.04.2 LTS | x86_64
Intel oneAPI classic | 2023.1 | macOS 12.6.3 (21G419) | x86_64

The following combinations are known to work, but they are not tested in the CI:

Name | Version | Platform | Architecture
--- | --- | --- | ---
GCC Fortran (MinGW) | 9.3.0, 10.2.0, 11.2.0 | Windows 10 | x86_64, i686
GCC Fortran (MinGW) | 9.3.0, 10.2.0, 11.2.0 | Windows 10 | x86_64

We try to test as many available compilers and platforms as possible.
A list of tested compilers which are currently not working and the respective issue are listed below.
Expand Down
7 changes: 1 addition & 6 deletions src/stdlib_linalg_norms.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -210,7 +210,6 @@ submodule(stdlib_linalg) stdlib_linalg_norms

integer(ilp) :: i
real(${rk}$) :: rorder
intrinsic :: abs, sum, sqrt, maxval, minval, conjg

! Initialize norm to zero
nrm = 0.0_${rk}$
Expand Down Expand Up @@ -286,8 +285,6 @@ submodule(stdlib_linalg) stdlib_linalg_norms

type(linalg_state_type) :: err_
integer(ilp) :: sze,norm_request
real(${rk}$) :: rorder
intrinsic :: abs, sum, sqrt, maxval, minval, conjg

sze = size(a,kind=ilp)

Expand Down Expand Up @@ -371,11 +368,9 @@ submodule(stdlib_linalg) stdlib_linalg_norms
type(linalg_state_type) :: err_
integer(ilp) :: sze,lda,norm_request,${loop_variables('j',rank-1,1)}$
logical :: contiguous_data
real(${rk}$) :: rorder
integer(ilp), dimension(${rank}$) :: spe,spack,perm,iperm
integer(ilp), dimension(${rank}$), parameter :: dim_range = [(lda,lda=1_ilp,${rank}$_ilp)]
${rt}$, allocatable :: apack${ranksuffix(rank)}$
intrinsic :: abs, sum, sqrt, norm2, maxval, minval, conjg

! Input matrix properties
sze = size (a,kind=ilp)
Expand Down Expand Up @@ -512,7 +507,7 @@ ${loop_variables_end(rank-1," "*12)}$
type(linalg_state_type), intent(out), optional :: err
type(linalg_state_type) :: err_
integer(ilp) :: j,m,n,lda,dims(2),norm_request,svd_errors
integer(ilp) :: m,n,lda,dims(2),svd_errors
integer(ilp), dimension(${rank}$) :: s,spack,perm,iperm
integer(ilp), dimension(${rank}$), parameter :: dim_range = [(m,m=1_ilp,${rank}$_ilp)]
integer(ilp) :: ${loop_variables('j',rank-2,2)}$
Expand Down
1 change: 0 additions & 1 deletion src/stdlib_sparse_conversion.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -460,7 +460,6 @@ contains

#:for k1, t1, s1 in (KINDS_TYPES)
recursive subroutine quicksort_i_${s1}$(a, b, first, last)
integer, parameter :: wp = sp
integer(ilp), intent(inout) :: a(*) !! reference table to sort
${t1}$, intent(inout) :: b(*) !! secondary real data to sort w.r.t. a
integer(ilp), intent(in) :: first, last
Expand Down

0 comments on commit 65175d7

Please sign in to comment.