Skip to content

Commit 427bc68

Browse files
authored
Fix warnings [-Wunused-xxx] from compilation (#879)
2 parents 8672fe1 + f749a16 commit 427bc68

24 files changed

+29
-38
lines changed

example/hashmaps/example_hashmaps_get_other_data.f90

+1-1
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
program example_get_other_data
22
use stdlib_kinds, only: int8, int64
3-
use stdlib_hashmaps, only: chaining_hashmap_type, int_index
3+
use stdlib_hashmaps, only: chaining_hashmap_type
44
use stdlib_hashmap_wrappers, only: fnv_1_hasher, key_type, other_type, set, get
55
implicit none
66
logical :: conflict

example/hashmaps/example_hashmaps_remove.f90

+1-1
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
program example_remove
22
use stdlib_kinds, only: int8, int64
3-
use stdlib_hashmaps, only: open_hashmap_type, int_index
3+
use stdlib_hashmaps, only: open_hashmap_type
44
use stdlib_hashmap_wrappers, only: fnv_1_hasher, &
55
fnv_1a_hasher, key_type, other_type, set
66
implicit none

example/hashmaps/example_hashmaps_set_other_data.f90

-1
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,4 @@
11
program example_set_other_data
2-
use stdlib_kinds, only: int8
32
use stdlib_hashmaps, only: open_hashmap_type
43
use stdlib_hashmap_wrappers, only: fnv_1_hasher, &
54
fnv_1a_hasher, key_type, other_type, set

example/linalg/example_determinant.f90

-1
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,6 @@ program example_determinant
22
use stdlib_kinds, only: dp
33
use stdlib_linalg, only: det, linalg_state_type
44
implicit none
5-
type(linalg_state_type) :: err
65

76
real(dp) :: d
87

example/linalg/example_eigvals.f90

-1
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,6 @@ program example_eigvals
33
use stdlib_linalg, only: eigvals
44
implicit none
55

6-
integer :: i
76
real, allocatable :: A(:,:),lambda(:)
87
complex, allocatable :: cA(:,:),clambda(:)
98

example/linalg/example_eigvalsh.f90

-1
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,6 @@ program example_eigvalsh
33
use stdlib_linalg, only: eigvalsh
44
implicit none
55

6-
integer :: i
76
real, allocatable :: A(:,:),lambda(:)
87
complex, allocatable :: cA(:,:)
98

example/linalg/example_state2.f90

-1
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,6 @@ program example_state2
77
use stdlib_linalg_state, only: linalg_state_type, LINALG_VALUE_ERROR, LINALG_SUCCESS, &
88
linalg_error_handling
99
implicit none
10-
integer :: info
1110
type(linalg_state_type) :: err
1211
real :: a_div_b
1312

example/selection/selection_vs_sort.f90

+1-1
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
program selection_vs_sort
2-
use stdlib_kinds, only: dp, sp, int64
2+
use stdlib_kinds, only: int64
33
use stdlib_selection, only: select, arg_select
44
use stdlib_sorting, only: sort
55
implicit none

src/stdlib_linalg_blas_c.fypp

-2
Original file line numberDiff line numberDiff line change
@@ -2549,8 +2549,6 @@ module stdlib_linalg_blas_c
25492549
! -- reference blas level1 routine --
25502550
! -- reference blas is a software package provided by univ. of tennessee, --
25512551
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
2552-
! Constants
2553-
integer, parameter :: wp = kind(1._sp)
25542552
! Scaling Constants
25552553
! Scalar Arguments
25562554
real(sp), intent(out) :: c

src/stdlib_linalg_blas_d.fypp

-4
Original file line numberDiff line numberDiff line change
@@ -848,7 +848,6 @@ module stdlib_linalg_blas_d
848848
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
849849
! march 2021
850850
! Constants
851-
integer, parameter :: wp = kind(1._dp)
852851
real(dp), parameter :: maxn = huge(0.0_dp)
853852
! .. blue's scaling constants ..
854853
! Scalar Arguments
@@ -985,8 +984,6 @@ module stdlib_linalg_blas_d
985984
! -- reference blas level1 routine --
986985
! -- reference blas is a software package provided by univ. of tennessee, --
987986
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
988-
! Constants
989-
integer, parameter :: wp = kind(1._dp)
990987
! Scaling Constants
991988
! Scalar Arguments
992989
real(dp), intent(inout) :: a, b
@@ -4422,7 +4419,6 @@ module stdlib_linalg_blas_d
44224419
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
44234420
! march 2021
44244421
! Constants
4425-
integer, parameter :: wp = kind(1._dp)
44264422
real(dp), parameter :: maxn = huge(0.0_dp)
44274423
! .. blue's scaling constants ..
44284424
! Scalar Arguments

src/stdlib_linalg_blas_q.fypp

-4
Original file line numberDiff line numberDiff line change
@@ -852,7 +852,6 @@ module stdlib_linalg_blas_${ri}$
852852
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
853853
! march 2021
854854
! Constants
855-
integer, parameter :: wp = kind(1._${rk}$)
856855
real(${rk}$), parameter :: maxn = huge(0.0_${rk}$)
857856
! .. blue's scaling constants ..
858857
! Scalar Arguments
@@ -989,8 +988,6 @@ module stdlib_linalg_blas_${ri}$
989988
! -- reference blas level1 routine --
990989
! -- reference blas is a software package provided by univ. of tennessee, --
991990
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
992-
! Constants
993-
integer, parameter :: wp = kind(1._${rk}$)
994991
! Scaling Constants
995992
! Scalar Arguments
996993
real(${rk}$), intent(inout) :: a, b
@@ -4426,7 +4423,6 @@ module stdlib_linalg_blas_${ri}$
44264423
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
44274424
! march 2021
44284425
! Constants
4429-
integer, parameter :: wp = kind(1._${rk}$)
44304426
real(${rk}$), parameter :: maxn = huge(0.0_${rk}$)
44314427
! .. blue's scaling constants ..
44324428
! Scalar Arguments

src/stdlib_linalg_blas_s.fypp

-3
Original file line numberDiff line numberDiff line change
@@ -233,7 +233,6 @@ module stdlib_linalg_blas_s
233233
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
234234
! march 2021
235235
! Constants
236-
integer, parameter :: wp = kind(1._sp)
237236
real(sp), parameter :: maxn = huge(0.0_sp)
238237
! .. blue's scaling constants ..
239238
! Scalar Arguments
@@ -1028,7 +1027,6 @@ module stdlib_linalg_blas_s
10281027
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
10291028
! march 2021
10301029
! Constants
1031-
integer, parameter :: wp = kind(1._sp)
10321030
real(sp), parameter :: maxn = huge(0.0_sp)
10331031
! .. blue's scaling constants ..
10341032
! Scalar Arguments
@@ -1166,7 +1164,6 @@ module stdlib_linalg_blas_s
11661164
! -- reference blas is a software package provided by univ. of tennessee, --
11671165
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
11681166
! Constants
1169-
integer, parameter :: wp = kind(1._sp)
11701167
! Scaling Constants
11711168
! Scalar Arguments
11721169
real(sp), intent(inout) :: a, b

src/stdlib_linalg_blas_w.fypp

-2
Original file line numberDiff line numberDiff line change
@@ -2635,8 +2635,6 @@ module stdlib_linalg_blas_${ci}$
26352635
! -- reference blas level1 routine --
26362636
! -- reference blas is a software package provided by univ. of tennessee, --
26372637
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
2638-
! Constants
2639-
integer, parameter :: wp = kind(1._${ck}$)
26402638
! Scaling Constants
26412639
! Scalar Arguments
26422640
real(${ck}$), intent(out) :: c

src/stdlib_linalg_blas_z.fypp

-2
Original file line numberDiff line numberDiff line change
@@ -2627,8 +2627,6 @@ module stdlib_linalg_blas_z
26272627
! -- reference blas level1 routine --
26282628
! -- reference blas is a software package provided by univ. of tennessee, --
26292629
! -- univ. of california berkeley, univ. of colorado denver and nag ltd..--
2630-
! Constants
2631-
integer, parameter :: wp = kind(1._dp)
26322630
! Scaling Constants
26332631
! Scalar Arguments
26342632
real(dp), intent(out) :: c

src/stdlib_linalg_cholesky.fypp

+1-1
Original file line numberDiff line numberDiff line change
@@ -54,7 +54,7 @@ submodule (stdlib_linalg) stdlib_linalg_cholesky
5454

5555
!> Local variables
5656
type(linalg_state_type) :: err0
57-
integer(ilp) :: lda,n,info,i,j
57+
integer(ilp) :: lda,n,info,j
5858
logical(lk) :: lower_,other_zeroed_
5959
character :: triangle
6060
${rt}$, parameter :: zero = 0.0_${rk}$

src/stdlib_linalg_eigenvalues.fypp

+8-3
Original file line numberDiff line numberDiff line change
@@ -162,14 +162,17 @@ submodule (stdlib_linalg) stdlib_linalg_eigenvalues
162162

163163
!> Local variables
164164
type(linalg_state_type) :: err0
165-
integer(ilp) :: m,n,lda,ldu,ldv,info,k,lwork,lrwork,neig
165+
integer(ilp) :: m,n,lda,ldu,ldv,info,k,lwork,neig
166166
logical(lk) :: copy_a
167167
character :: task_u,task_v
168168
${rt}$, target :: work_dummy(1),u_dummy(1,1),v_dummy(1,1)
169169
${rt}$, allocatable :: work(:)
170+
${rt}$, pointer :: amat(:,:),umat(:,:),vmat(:,:)
171+
#:if rt.startswith('complex')
170172
real(${rk}$), allocatable :: rwork(:)
171-
${rt}$, pointer :: amat(:,:),lreal(:),limag(:),umat(:,:),vmat(:,:)
172-
173+
#:else
174+
${rt}$, pointer :: lreal(:),limag(:)
175+
#:endif
173176
!> Matrix size
174177
m = size(a,1,kind=ilp)
175178
n = size(a,2,kind=ilp)
@@ -388,7 +391,9 @@ submodule (stdlib_linalg) stdlib_linalg_eigenvalues
388391
character :: triangle,task
389392
${rt}$, target :: work_dummy(1)
390393
${rt}$, allocatable :: work(:)
394+
#:if rt.startswith('complex')
391395
real(${rk}$), allocatable :: rwork(:)
396+
#:endif
392397
${rt}$, pointer :: amat(:,:)
393398

394399
!> Matrix size

src/stdlib_linalg_lapack_c.fypp

+1-1
Original file line numberDiff line numberDiff line change
@@ -38666,7 +38666,7 @@ module stdlib_linalg_lapack_c
3866638666
! Local Scalars
3866738667
integer(ilp) :: ncols, i, j, k, kp
3866838668
real(sp) :: amax, umax, rpvgrw, tmp
38669-
logical(lk) :: upper, lsame
38669+
logical(lk) :: upper
3867038670
complex(sp) :: zdum
3867138671
! Intrinsic Functions
3867238672
intrinsic :: abs,real,aimag,max,min

src/stdlib_linalg_lapack_d.fypp

+1-1
Original file line numberDiff line numberDiff line change
@@ -6042,7 +6042,7 @@ module stdlib_linalg_lapack_d
60426042

60436043

60446044
! Local Scalars
6045-
integer(ilp) :: i, i1, i2, i3, i4, it1, it2, it3, it4, j
6045+
integer(ilp) :: i, i1, i2, i3, i4, it1, it2, it3, it4
60466046
! Local Arrays
60476047
integer(ilp) :: mm(lv,4)
60486048
! Intrinsic Functions

src/stdlib_linalg_lapack_s.fypp

+1-1
Original file line numberDiff line numberDiff line change
@@ -6071,7 +6071,7 @@ module stdlib_linalg_lapack_s
60716071

60726072

60736073
! Local Scalars
6074-
integer(ilp) :: i, i1, i2, i3, i4, it1, it2, it3, it4, j
6074+
integer(ilp) :: i, i1, i2, i3, i4, it1, it2, it3, it4
60756075
! Local Arrays
60766076
integer(ilp) :: mm(lv,4)
60776077
! Intrinsic Functions

src/stdlib_linalg_lapack_w.fypp

+1-1
Original file line numberDiff line numberDiff line change
@@ -35519,7 +35519,7 @@ module stdlib_linalg_lapack_${ci}$
3551935519
! Local Scalars
3552035520
integer(ilp) :: ncols, i, j, k, kp
3552135521
real(${ck}$) :: amax, umax, rpvgrw, tmp
35522-
logical(lk) :: upper, lsame
35522+
logical(lk) :: upper
3552335523
complex(${ck}$) :: zdum
3552435524
! Intrinsic Functions
3552535525
intrinsic :: abs,real,aimag,max,min

src/stdlib_linalg_lapack_z.fypp

+1-1
Original file line numberDiff line numberDiff line change
@@ -39073,7 +39073,7 @@ module stdlib_linalg_lapack_z
3907339073
! Local Scalars
3907439074
integer(ilp) :: ncols, i, j, k, kp
3907539075
real(dp) :: amax, umax, rpvgrw, tmp
39076-
logical(lk) :: upper, lsame
39076+
logical(lk) :: upper
3907739077
complex(dp) :: zdum
3907839078
! Intrinsic Functions
3907939079
intrinsic :: abs,real,aimag,max,min

src/stdlib_linalg_least_squares.fypp

+8-2
Original file line numberDiff line numberDiff line change
@@ -203,12 +203,18 @@ submodule (stdlib_linalg) stdlib_linalg_least_squares
203203
!! Local variables
204204
type(linalg_state_type) :: err0
205205
integer(ilp) :: m,n,lda,ldb,nrhs,ldx,nrhsx,info,mnmin,mnmax,arank,lrwork,liwork,lcwork
206-
integer(ilp) :: nrs,nis,ncs,nsvd
206+
integer(ilp) :: nrs,nis,nsvd
207+
#:if rt.startswith('complex')
208+
integer(ilp) :: ncs
209+
#:endif
207210
integer(ilp), pointer :: iwork(:)
208211
logical(lk) :: copy_a,large_enough_x
209212
real(${rk}$) :: acond,rcond
210213
real(${rk}$), pointer :: rwork(:),singular(:)
211-
${rt}$, pointer :: xmat(:,:),amat(:,:),cwork(:)
214+
${rt}$, pointer :: xmat(:,:),amat(:,:)
215+
#:if rt.startswith('complex')
216+
${rt}$, pointer :: cwork(:)
217+
#:endif
212218

213219
! Problem sizes
214220
m = size(a,1,kind=ilp)

src/stdlib_linalg_svd.fypp

+2
Original file line numberDiff line numberDiff line change
@@ -147,7 +147,9 @@ submodule(stdlib_linalg) stdlib_linalg_svd
147147
character :: task
148148
${rt}$, target :: work_dummy(1),u_dummy(1,1),vt_dummy(1,1)
149149
${rt}$, allocatable :: work(:)
150+
#:if rt.startswith('complex')
150151
real(${rk}$), allocatable :: rwork(:)
152+
#:endif
151153
${rt}$, pointer :: amat(:,:),umat(:,:),vtmat(:,:)
152154

153155
!> Matrix determinant size

src/stdlib_specialfunctions_gamma.fypp

+2-2
Original file line numberDiff line numberDiff line change
@@ -232,7 +232,7 @@ contains
232232
integer :: i
233233

234234
real(${k1}$), parameter :: zero_k1 = 0.0_${k1}$
235-
${t2}$, parameter :: zero = 0.0_${k2}$, half = 0.5_${k2}$, &
235+
${t2}$, parameter :: half = 0.5_${k2}$, &
236236
one = 1.0_${k2}$, pi = acos(- one), sqpi = sqrt(pi)
237237
complex(${k2}$) :: y, x, sum
238238

@@ -714,7 +714,7 @@ contains
714714
${t1}$, intent(in) :: p
715715
${t2}$, intent(in) :: x
716716
${t2}$ :: res, p_lim, a, b, g, c, d, y
717-
integer :: n, m
717+
integer :: n
718718
${t2}$, parameter :: zero = 0.0_${k2}$, one = 1.0_${k2}$
719719
${t2}$, parameter :: dm = tiny(1.0_${k2}$) * 10 ** 6
720720
${t1}$, parameter :: zero_k1 = 0_${k1}$, two = 2_${k1}$

0 commit comments

Comments
 (0)