@@ -73,8 +73,8 @@ subroutine test_eye
7373 msg= " sum(rye - diag([(1.0_sp,i=1,6)])) < sptol failed." ,warn= warn)
7474
7575 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)
7878 end subroutine
7979
8080 subroutine test_diag_rsp
@@ -153,7 +153,7 @@ subroutine test_diag_rqp
153153 subroutine test_diag_csp
154154 integer , parameter :: n = 3
155155 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 )
157157 integer :: i,j
158158 write (* ,* ) " test_diag_csp"
159159 a = diag([(i,i= 1 ,n)]) + diag([(i_,i= 1 ,n)])
@@ -170,7 +170,7 @@ subroutine test_diag_csp
170170 subroutine test_diag_cdp
171171 integer , parameter :: n = 3
172172 complex (dp) :: a(n,n)
173- complex (dp), parameter :: i_ = cmplx (0 ,1 )
173+ complex (dp), parameter :: i_ = cmplx (0 ,1 ,kind = dp )
174174 write (* ,* ) " test_diag_cdp"
175175 a = diag([i_],- 2 ) + diag([i_],2 )
176176 call check(a(3 ,1 ) == i_ .and. a(1 ,3 ) == i_, &
@@ -180,7 +180,7 @@ subroutine test_diag_cdp
180180 subroutine test_diag_cqp
181181 integer , parameter :: n = 3
182182 complex (qp) :: a(n,n)
183- complex (qp), parameter :: i_ = cmplx (0 ,1 )
183+ complex (qp), parameter :: i_ = cmplx (0 ,1 ,kind = qp )
184184 write (* ,* ) " test_diag_cqp"
185185 a = diag([i_,i_],- 1 ) + diag([i_,i_],1 )
186186 call check(all (diag(a,- 1 ) == i_) .and. all (diag(a,1 ) == i_), &
@@ -331,7 +331,7 @@ subroutine test_trace_csp
331331 integer , parameter :: n = 5
332332 real (sp) :: re(n,n), im(n,n)
333333 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 )
335335 write (* ,* ) " test_trace_csp"
336336
337337 call random_number (re)
@@ -350,12 +350,12 @@ subroutine test_trace_csp
350350 subroutine test_trace_cdp
351351 integer , parameter :: n = 3
352352 complex (dp) :: a(n,n), ans
353- complex (dp), parameter :: i_ = cmplx (0 ,1 )
353+ complex (dp), parameter :: i_ = cmplx (0 ,1 ,kind = dp )
354354 integer :: j
355355 write (* ,* ) " test_trace_cdp"
356356
357357 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
359359
360360 call check(abs (trace(a) - ans) < dptol, &
361361 msg= " abs(trace(a) - ans) < dptol failed." ,warn= warn)
@@ -364,7 +364,7 @@ subroutine test_trace_cdp
364364 subroutine test_trace_cqp
365365 integer , parameter :: n = 3
366366 complex (qp) :: a(n,n)
367- complex (qp), parameter :: i_ = cmplx (0 ,1 )
367+ complex (qp), parameter :: i_ = cmplx (0 ,1 ,kind = qp )
368368 write (* ,* ) " test_trace_cqp"
369369 a = 3 * eye(n) + 4 * eye(n)* i_ ! pythagorean triple
370370 call check(abs (trace(a)) - 3 * 5.0_qp < qptol, &
0 commit comments