Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
8 changes: 4 additions & 4 deletions src/stdlib_experimental_stats_mean.fypp
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ contains
${t1}$ :: res

if (.not.optval(mask, .true.)) then
res = ieee_value(real(res, kind=${k1}$), ieee_quiet_nan)
res = ieee_value(1._${k1}$, ieee_quiet_nan)
Copy link
Member Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Note: this line (as written before) generated a Run-Time Check Failure with ifort because res is used without being defined.

return
end if

Expand All @@ -38,7 +38,7 @@ contains
real(dp) :: res

if (.not.optval(mask, .true.)) then
res = ieee_value(res, ieee_quiet_nan)
res = ieee_value(1._dp, ieee_quiet_nan)
return
end if

Expand All @@ -59,7 +59,7 @@ contains
${t1}$ :: res${reduced_shape('x', rank, 'dim')}$

if (.not.optval(mask, .true.)) then
res = ieee_value(real(res, kind=${k1}$), ieee_quiet_nan)
res = ieee_value(1._${k1}$, ieee_quiet_nan)
return
end if

Expand All @@ -84,7 +84,7 @@ contains
real(dp) :: res${reduced_shape('x', rank, 'dim')}$

if (.not.optval(mask, .true.)) then
res = ieee_value(res, ieee_quiet_nan)
res = ieee_value(1._dp, ieee_quiet_nan)
return
end if

Expand Down
1 change: 0 additions & 1 deletion src/tests/ascii/test_ascii.f90
Original file line number Diff line number Diff line change
Expand Up @@ -486,7 +486,6 @@ subroutine test_to_upper_long()
!
subroutine test_ascii_table
integer :: i, j
character(len=1) :: c
logical :: table(15,12)

abstract interface
Expand Down
8 changes: 3 additions & 5 deletions src/tests/linalg/test_linalg.f90
Original file line number Diff line number Diff line change
Expand Up @@ -152,7 +152,7 @@ subroutine test_diag_rqp

subroutine test_diag_csp
integer, parameter :: n = 3
complex(sp) :: v(n), a(n,n), b(n,n)
complex(sp) :: a(n,n), b(n,n)
complex(sp), parameter :: i_ = cmplx(0,1,kind=sp)
integer :: i,j
write(*,*) "test_diag_csp"
Expand All @@ -169,9 +169,8 @@ subroutine test_diag_csp

subroutine test_diag_cdp
integer, parameter :: n = 3
complex(dp) :: v(n), a(n,n), b(n,n)
complex(dp) :: a(n,n)
complex(dp), parameter :: i_ = cmplx(0,1,kind=dp)
integer :: i,j
write(*,*) "test_diag_cdp"
a = diag([i_],-2) + diag([i_],2)
call check(a(3,1) == i_ .and. a(1,3) == i_, &
Expand All @@ -180,9 +179,8 @@ subroutine test_diag_cdp

subroutine test_diag_cqp
integer, parameter :: n = 3
complex(qp) :: v(n), a(n,n), b(n,n)
complex(qp) :: a(n,n)
complex(qp), parameter :: i_ = cmplx(0,1,kind=qp)
integer :: i,j
write(*,*) "test_diag_cqp"
a = diag([i_,i_],-1) + diag([i_,i_],1)
call check(all(diag(a,-1) == i_) .and. all(diag(a,1) == i_), &
Expand Down