@@ -73,8 +73,8 @@ subroutine test_eye
73
73
msg= " sum(rye - diag([(1.0_sp,i=1,6)])) < sptol failed." ,warn= warn)
74
74
75
75
cye = eye(7 )
76
- call check(abs (trace(cye) - cmplx (7.0_sp ,0.0_sp )) < sptol, &
77
- msg= " abs(trace(cye) - cmplx(7.0_sp,0.0_sp)) < sptol failed." ,warn= warn)
76
+ call check(abs (trace(cye) - cmplx (7.0_sp ,0.0_sp ,kind = sp )) < sptol, &
77
+ msg= " abs(trace(cye) - cmplx(7.0_sp,0.0_sp,kind=sp )) < sptol failed." ,warn= warn)
78
78
end subroutine
79
79
80
80
subroutine test_diag_rsp
@@ -153,7 +153,7 @@ subroutine test_diag_rqp
153
153
subroutine test_diag_csp
154
154
integer , parameter :: n = 3
155
155
complex (sp) :: a(n,n), b(n,n)
156
- complex (sp), parameter :: i_ = cmplx (0 ,1 )
156
+ complex (sp), parameter :: i_ = cmplx (0 ,1 ,kind = sp )
157
157
integer :: i,j
158
158
write (* ,* ) " test_diag_csp"
159
159
a = diag([(i,i= 1 ,n)]) + diag([(i_,i= 1 ,n)])
@@ -170,7 +170,7 @@ subroutine test_diag_csp
170
170
subroutine test_diag_cdp
171
171
integer , parameter :: n = 3
172
172
complex (dp) :: a(n,n)
173
- complex (dp), parameter :: i_ = cmplx (0 ,1 )
173
+ complex (dp), parameter :: i_ = cmplx (0 ,1 ,kind = dp )
174
174
write (* ,* ) " test_diag_cdp"
175
175
a = diag([i_],- 2 ) + diag([i_],2 )
176
176
call check(a(3 ,1 ) == i_ .and. a(1 ,3 ) == i_, &
@@ -180,7 +180,7 @@ subroutine test_diag_cdp
180
180
subroutine test_diag_cqp
181
181
integer , parameter :: n = 3
182
182
complex (qp) :: a(n,n)
183
- complex (qp), parameter :: i_ = cmplx (0 ,1 )
183
+ complex (qp), parameter :: i_ = cmplx (0 ,1 ,kind = qp )
184
184
write (* ,* ) " test_diag_cqp"
185
185
a = diag([i_,i_],- 1 ) + diag([i_,i_],1 )
186
186
call check(all (diag(a,- 1 ) == i_) .and. all (diag(a,1 ) == i_), &
@@ -331,7 +331,7 @@ subroutine test_trace_csp
331
331
integer , parameter :: n = 5
332
332
real (sp) :: re(n,n), im(n,n)
333
333
complex (sp) :: a(n,n), b(n,n)
334
- complex (sp), parameter :: i_ = cmplx (0 ,1 )
334
+ complex (sp), parameter :: i_ = cmplx (0 ,1 ,kind = sp )
335
335
write (* ,* ) " test_trace_csp"
336
336
337
337
call random_number (re)
@@ -350,12 +350,12 @@ subroutine test_trace_csp
350
350
subroutine test_trace_cdp
351
351
integer , parameter :: n = 3
352
352
complex (dp) :: a(n,n), ans
353
- complex (dp), parameter :: i_ = cmplx (0 ,1 )
353
+ complex (dp), parameter :: i_ = cmplx (0 ,1 ,kind = dp )
354
354
integer :: j
355
355
write (* ,* ) " test_trace_cdp"
356
356
357
357
a = reshape ([(j + (n** 2 - (j-1 ))* i_,j= 1 ,n** 2 )],[n,n])
358
- ans = cmplx (15 ,15 ) ! (1 + 5 + 9) + (9 + 5 + 1)i
358
+ ans = cmplx (15 ,15 ,kind = dp ) ! (1 + 5 + 9) + (9 + 5 + 1)i
359
359
360
360
call check(abs (trace(a) - ans) < dptol, &
361
361
msg= " abs(trace(a) - ans) < dptol failed." ,warn= warn)
@@ -364,7 +364,7 @@ subroutine test_trace_cdp
364
364
subroutine test_trace_cqp
365
365
integer , parameter :: n = 3
366
366
complex (qp) :: a(n,n)
367
- complex (qp), parameter :: i_ = cmplx (0 ,1 )
367
+ complex (qp), parameter :: i_ = cmplx (0 ,1 ,kind = qp )
368
368
write (* ,* ) " test_trace_cqp"
369
369
a = 3 * eye(n) + 4 * eye(n)* i_ ! pythagorean triple
370
370
call check(abs (trace(a)) - 3 * 5.0_qp < qptol, &
0 commit comments