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/tests/io/test_savetxt.f90
Original file line number Diff line number Diff line change
Expand Up @@ -86,13 +86,13 @@ subroutine test_csp(outpath)
character(*), intent(in) :: outpath
complex(sp) :: d(3, 2), e(2, 3)
complex(sp), allocatable :: d2(:, :)
d = cmplx(1, 1)* reshape([1, 2, 3, 4, 5, 6], [3, 2])
d = cmplx(1, 1,kind=sp)* reshape([1, 2, 3, 4, 5, 6], [3, 2])
call savetxt(outpath, d)
call loadtxt(outpath, d2)
call check(all(shape(d2) == [3, 2]))
call check(all(abs(d-d2) < epsilon(1._sp)))

e = cmplx(1, 1)* reshape([1, 2, 3, 4, 5, 6], [2, 3])
e = cmplx(1, 1,kind=sp)* reshape([1, 2, 3, 4, 5, 6], [2, 3])
call savetxt(outpath, e)
call loadtxt(outpath, d2)
call check(all(shape(d2) == [2, 3]))
Expand All @@ -103,13 +103,13 @@ subroutine test_cdp(outpath)
character(*), intent(in) :: outpath
complex(dp) :: d(3, 2), e(2, 3)
complex(dp), allocatable :: d2(:, :)
d = cmplx(1._dp, 1._dp)* reshape([1, 2, 3, 4, 5, 6], [3, 2])
d = cmplx(1._dp, 1._dp,kind=dp)* reshape([1, 2, 3, 4, 5, 6], [3, 2])
call savetxt(outpath, d)
call loadtxt(outpath, d2)
call check(all(shape(d2) == [3, 2]))
call check(all(abs(d-d2) < epsilon(1._dp)))

e = cmplx(1, 1)* reshape([1, 2, 3, 4, 5, 6], [2, 3])
e = cmplx(1, 1,kind=dp)* reshape([1, 2, 3, 4, 5, 6], [2, 3])
call savetxt(outpath, e)
call loadtxt(outpath, d2)
call check(all(shape(d2) == [2, 3]))
Expand Down
18 changes: 9 additions & 9 deletions src/tests/linalg/test_linalg.f90
Original file line number Diff line number Diff line change
Expand Up @@ -73,8 +73,8 @@ subroutine test_eye
msg="sum(rye - diag([(1.0_sp,i=1,6)])) < sptol failed.",warn=warn)

cye = eye(7)
call check(abs(trace(cye) - cmplx(7.0_sp,0.0_sp)) < sptol, &
msg="abs(trace(cye) - cmplx(7.0_sp,0.0_sp)) < sptol failed.",warn=warn)
call check(abs(trace(cye) - cmplx(7.0_sp,0.0_sp,kind=sp)) < sptol, &
msg="abs(trace(cye) - cmplx(7.0_sp,0.0_sp,kind=sp)) < sptol failed.",warn=warn)
end subroutine

subroutine test_diag_rsp
Expand Down Expand Up @@ -153,7 +153,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), parameter :: i_ = cmplx(0,1)
complex(sp), parameter :: i_ = cmplx(0,1,kind=sp)
integer :: i,j
write(*,*) "test_diag_csp"
a = diag([(i,i=1,n)]) + diag([(i_,i=1,n)])
Expand All @@ -170,7 +170,7 @@ subroutine test_diag_csp
subroutine test_diag_cdp
integer, parameter :: n = 3
complex(dp) :: v(n), a(n,n), b(n,n)
complex(dp), parameter :: i_ = cmplx(0,1)
complex(dp), parameter :: i_ = cmplx(0,1,kind=dp)
integer :: i,j
write(*,*) "test_diag_cdp"
a = diag([i_],-2) + diag([i_],2)
Expand All @@ -181,7 +181,7 @@ subroutine test_diag_cdp
subroutine test_diag_cqp
integer, parameter :: n = 3
complex(qp) :: v(n), a(n,n), b(n,n)
complex(qp), parameter :: i_ = cmplx(0,1)
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)
Expand Down Expand Up @@ -333,7 +333,7 @@ subroutine test_trace_csp
integer, parameter :: n = 5
real(sp) :: re(n,n), im(n,n)
complex(sp) :: a(n,n), b(n,n)
complex(sp), parameter :: i_ = cmplx(0,1)
complex(sp), parameter :: i_ = cmplx(0,1,kind=sp)
write(*,*) "test_trace_csp"

call random_number(re)
Expand All @@ -352,12 +352,12 @@ subroutine test_trace_csp
subroutine test_trace_cdp
integer, parameter :: n = 3
complex(dp) :: a(n,n), ans
complex(dp), parameter :: i_ = cmplx(0,1)
complex(dp), parameter :: i_ = cmplx(0,1,kind=dp)
integer :: j
write(*,*) "test_trace_cdp"

a = reshape([(j + (n**2 - (j-1))*i_,j=1,n**2)],[n,n])
ans = cmplx(15,15) !(1 + 5 + 9) + (9 + 5 + 1)i
ans = cmplx(15,15,kind=dp) !(1 + 5 + 9) + (9 + 5 + 1)i

call check(abs(trace(a) - ans) < dptol, &
msg="abs(trace(a) - ans) < dptol failed.",warn=warn)
Expand All @@ -366,7 +366,7 @@ subroutine test_trace_cdp
subroutine test_trace_cqp
integer, parameter :: n = 3
complex(qp) :: a(n,n)
complex(qp), parameter :: i_ = cmplx(0,1)
complex(qp), parameter :: i_ = cmplx(0,1,kind=qp)
write(*,*) "test_trace_cqp"
a = 3*eye(n) + 4*eye(n)*i_ ! pythagorean triple
call check(abs(trace(a)) - 3*5.0_qp < qptol, &
Expand Down
2 changes: 1 addition & 1 deletion src/tests/optval/test_optval.f90
Original file line number Diff line number Diff line change
Expand Up @@ -100,7 +100,7 @@ function foo_csp(x) result(z)
subroutine test_optval_cdp
complex(dp) :: z1
print *, "test_optval_cdp"
z1 = cmplx(1.0_dp, 2.0_dp)
z1 = cmplx(1.0_dp, 2.0_dp,kind=dp)
call check(foo_cdp(z1) == z1)
call check(foo_cdp() == z1)
end subroutine test_optval_cdp
Expand Down
22 changes: 11 additions & 11 deletions src/tests/stats/test_cov.f90
Original file line number Diff line number Diff line change
Expand Up @@ -14,17 +14,17 @@ program test_cov
2._dp, 4._dp, 6._dp, 8._dp,&
9._dp, 10._dp, 11._dp, 12._dp], [4, 3])

complex(dp) :: cd1(5) = [ cmplx(0.57706_dp, 0.00000_dp),&
cmplx(0.00000_dp, 1.44065_dp),&
cmplx(1.26401_dp, 0.00000_dp),&
cmplx(0.00000_dp, 0.88833_dp),&
cmplx(1.14352_dp, 0.00000_dp)]
complex(dp) :: ds(2,3) = reshape([ cmplx(1._dp, 0._dp),&
cmplx(0._dp, 2._dp),&
cmplx(3._dp, 0._dp),&
cmplx(0._dp, 4._dp),&
cmplx(5._dp, 0._dp),&
cmplx(0._dp, 6._dp)], [2, 3])
complex(dp) :: cd1(5) = [ cmplx(0.57706_dp, 0.00000_dp,kind=dp),&
cmplx(0.00000_dp, 1.44065_dp,kind=dp),&
cmplx(1.26401_dp, 0.00000_dp,kind=dp),&
cmplx(0.00000_dp, 0.88833_dp,kind=dp),&
cmplx(1.14352_dp, 0.00000_dp,kind=dp)]
complex(dp) :: ds(2,3) = reshape([ cmplx(1._dp, 0._dp,kind=dp),&
cmplx(0._dp, 2._dp,kind=dp),&
cmplx(3._dp, 0._dp,kind=dp),&
cmplx(0._dp, 4._dp,kind=dp),&
cmplx(5._dp, 0._dp,kind=dp),&
cmplx(0._dp, 6._dp,kind=dp)], [2, 3])


call test_sp(real(d1, sp), real(d, sp))
Expand Down
6 changes: 3 additions & 3 deletions src/tests/stats/test_mean.f90
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ program test_mean
!csp

call loadtxt("array3.dat", d)
cs = cmplx(1._sp, 1._sp)*d
cs = cmplx(1._sp, 1._sp,kind=sp)*d

call check( abs(mean(cs) - sum(cs)/real(size(cs), sp)) < sptol)
call check( sum( abs( mean(cs,1) - sum(cs,1)/real(size(cs,1), sp) )) < sptol)
Expand All @@ -53,7 +53,7 @@ program test_mean
!cdp

call loadtxt("array3.dat", d)
cd = cmplx(1._dp, 1._dp)*d
cd = cmplx(1._dp, 1._dp,kind=dp)*d

call check( abs(mean(cd) - sum(cd)/real(size(cd), dp)) < dptol)
call check( sum( abs( mean(cd,1) - sum(cd,1)/real(size(cd,1), dp) )) < dptol)
Expand Down Expand Up @@ -102,7 +102,7 @@ program test_mean
cd3(:,:,1)=d;
cd3(:,:,2)=d*1.5;
cd3(:,:,3)=d*4;
cd3 = cmplx(1._sp, 1._sp)*cd3
cd3 = cmplx(1._sp, 1._sp,kind=sp)*cd3

call check( abs(mean(cd3) - sum(cd3)/real(size(cd3), dp)) < dptol)
call check( sum( abs( mean(cd3,1) - sum(cd3,1)/real(size(cd3,1), dp) )) < dptol)
Expand Down
10 changes: 5 additions & 5 deletions src/tests/stats/test_var.f90
Original file line number Diff line number Diff line change
Expand Up @@ -30,11 +30,11 @@ program test_var
cmplx(1.26401_sp, 0.00000_sp),&
cmplx(0.00000_sp, 0.88833_sp),&
cmplx(1.14352_sp, 0.00000_sp)]
complex(dp) :: cd1(5) = [ cmplx(0.57706_dp, 0.00000_dp),&
cmplx(0.00000_dp, 1.44065_dp),&
cmplx(1.26401_dp, 0.00000_dp),&
cmplx(0.00000_dp, 0.88833_dp),&
cmplx(1.14352_dp, 0.00000_dp)]
complex(dp) :: cd1(5) = [ cmplx(0.57706_dp, 0.00000_dp,kind=dp),&
cmplx(0.00000_dp, 1.44065_dp,kind=dp),&
cmplx(1.26401_dp, 0.00000_dp,kind=dp),&
cmplx(0.00000_dp, 0.88833_dp,kind=dp),&
cmplx(1.14352_dp, 0.00000_dp,kind=dp)]
complex(sp) :: cs(5,3)
complex(dp) :: cd(5,3)

Expand Down
10 changes: 5 additions & 5 deletions src/tests/stats/test_varn.f90
Original file line number Diff line number Diff line change
Expand Up @@ -23,11 +23,11 @@ program test_varn
9._dp, 10._dp, 11._dp, 12._dp], [4, 3])


complex(dp) :: cd1(5) = [ cmplx(0.57706_dp, 0.00000_dp),&
cmplx(0.00000_dp, 1.44065_dp),&
cmplx(1.26401_dp, 0.00000_dp),&
cmplx(0.00000_dp, 0.88833_dp),&
cmplx(1.14352_dp, 0.00000_dp)]
complex(dp) :: cd1(5) = [ cmplx(0.57706_dp, 0.00000_dp,kind=dp),&
cmplx(0.00000_dp, 1.44065_dp,kind=dp),&
cmplx(1.26401_dp, 0.00000_dp,kind=dp),&
cmplx(0.00000_dp, 0.88833_dp,kind=dp),&
cmplx(1.14352_dp, 0.00000_dp,kind=dp)]
complex(dp) :: cd(5,3)


Expand Down