@@ -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) - complex (7.0_sp ,0.0_sp )) < sptol, &
77- msg= " abs(trace(cye) - complex (7.0_sp,0.0_sp)) < sptol failed." ,warn= warn)
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)
7878 end subroutine
7979
8080 subroutine test_diag_rsp
@@ -152,8 +152,8 @@ subroutine test_diag_rqp
152152
153153 subroutine test_diag_csp
154154 integer , parameter :: n = 3
155- complex (sp) :: v(n), a(n,n), b(n,n)
156- complex (sp), parameter :: i_ = complex (0 ,1 )
155+ complex (sp) :: a(n,n), b(n,n)
156+ complex (sp), parameter :: i_ = cmplx (0 ,1 )
157157 integer :: i,j
158158 write (* ,* ) " test_diag_csp"
159159 a = diag([(i,i= 1 ,n)]) + diag([(i_,i= 1 ,n)])
@@ -169,9 +169,8 @@ subroutine test_diag_csp
169169
170170 subroutine test_diag_cdp
171171 integer , parameter :: n = 3
172- complex (dp) :: v(n), a(n,n), b(n,n)
173- complex (dp), parameter :: i_ = complex (0 ,1 )
174- integer :: i,j
172+ complex (dp) :: a(n,n)
173+ complex (dp), parameter :: i_ = cmplx (0 ,1 )
175174 write (* ,* ) " test_diag_cdp"
176175 a = diag([i_],- 2 ) + diag([i_],2 )
177176 call check(a(3 ,1 ) == i_ .and. a(1 ,3 ) == i_, &
@@ -180,9 +179,8 @@ subroutine test_diag_cdp
180179
181180 subroutine test_diag_cqp
182181 integer , parameter :: n = 3
183- complex (qp) :: v(n), a(n,n), b(n,n)
184- complex (qp), parameter :: i_ = complex (0 ,1 )
185- integer :: i,j
182+ complex (qp) :: a(n,n)
183+ complex (qp), parameter :: i_ = cmplx (0 ,1 )
186184 write (* ,* ) " test_diag_cqp"
187185 a = diag([i_,i_],- 1 ) + diag([i_,i_],1 )
188186 call check(all (diag(a,- 1 ) == i_) .and. all (diag(a,1 ) == i_), &
@@ -333,7 +331,7 @@ subroutine test_trace_csp
333331 integer , parameter :: n = 5
334332 real (sp) :: re(n,n), im(n,n)
335333 complex (sp) :: a(n,n), b(n,n)
336- complex (sp), parameter :: i_ = complex (0 ,1 )
334+ complex (sp), parameter :: i_ = cmplx (0 ,1 )
337335 write (* ,* ) " test_trace_csp"
338336
339337 call random_number (re)
@@ -352,12 +350,12 @@ subroutine test_trace_csp
352350 subroutine test_trace_cdp
353351 integer , parameter :: n = 3
354352 complex (dp) :: a(n,n), ans
355- complex (dp), parameter :: i_ = complex (0 ,1 )
353+ complex (dp), parameter :: i_ = cmplx (0 ,1 )
356354 integer :: j
357355 write (* ,* ) " test_trace_cdp"
358356
359357 a = reshape ([(j + (n** 2 - (j-1 ))* i_,j= 1 ,n** 2 )],[n,n])
360- ans = complex (15 ,15 ) ! (1 + 5 + 9) + (9 + 5 + 1)i
358+ ans = cmplx (15 ,15 ) ! (1 + 5 + 9) + (9 + 5 + 1)i
361359
362360 call check(abs (trace(a) - ans) < dptol, &
363361 msg= " abs(trace(a) - ans) < dptol failed." ,warn= warn)
@@ -366,7 +364,7 @@ subroutine test_trace_cdp
366364 subroutine test_trace_cqp
367365 integer , parameter :: n = 3
368366 complex (qp) :: a(n,n)
369- complex (qp), parameter :: i_ = complex (0 ,1 )
367+ complex (qp), parameter :: i_ = cmplx (0 ,1 )
370368 write (* ,* ) " test_trace_cqp"
371369 a = 3 * eye(n) + 4 * eye(n)* i_ ! pythagorean triple
372370 call check(abs (trace(a)) - 3 * 5.0_qp < qptol, &
@@ -442,4 +440,4 @@ pure recursive function catalan_number(n) result(value)
442440 end if
443441 end function
444442
445- end program
443+ end program
0 commit comments