@@ -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) - 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)
78
78
end subroutine
79
79
80
80
subroutine test_diag_rsp
@@ -152,8 +152,8 @@ subroutine test_diag_rqp
152
152
153
153
subroutine test_diag_csp
154
154
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 )
157
157
integer :: i,j
158
158
write (* ,* ) " test_diag_csp"
159
159
a = diag([(i,i= 1 ,n)]) + diag([(i_,i= 1 ,n)])
@@ -169,9 +169,8 @@ subroutine test_diag_csp
169
169
170
170
subroutine test_diag_cdp
171
171
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 )
175
174
write (* ,* ) " test_diag_cdp"
176
175
a = diag([i_],- 2 ) + diag([i_],2 )
177
176
call check(a(3 ,1 ) == i_ .and. a(1 ,3 ) == i_, &
@@ -180,9 +179,8 @@ subroutine test_diag_cdp
180
179
181
180
subroutine test_diag_cqp
182
181
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 )
186
184
write (* ,* ) " test_diag_cqp"
187
185
a = diag([i_,i_],- 1 ) + diag([i_,i_],1 )
188
186
call check(all (diag(a,- 1 ) == i_) .and. all (diag(a,1 ) == i_), &
@@ -333,7 +331,7 @@ subroutine test_trace_csp
333
331
integer , parameter :: n = 5
334
332
real (sp) :: re(n,n), im(n,n)
335
333
complex (sp) :: a(n,n), b(n,n)
336
- complex (sp), parameter :: i_ = complex (0 ,1 )
334
+ complex (sp), parameter :: i_ = cmplx (0 ,1 )
337
335
write (* ,* ) " test_trace_csp"
338
336
339
337
call random_number (re)
@@ -352,12 +350,12 @@ subroutine test_trace_csp
352
350
subroutine test_trace_cdp
353
351
integer , parameter :: n = 3
354
352
complex (dp) :: a(n,n), ans
355
- complex (dp), parameter :: i_ = complex (0 ,1 )
353
+ complex (dp), parameter :: i_ = cmplx (0 ,1 )
356
354
integer :: j
357
355
write (* ,* ) " test_trace_cdp"
358
356
359
357
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
361
359
362
360
call check(abs (trace(a) - ans) < dptol, &
363
361
msg= " abs(trace(a) - ans) < dptol failed." ,warn= warn)
@@ -366,7 +364,7 @@ subroutine test_trace_cdp
366
364
subroutine test_trace_cqp
367
365
integer , parameter :: n = 3
368
366
complex (qp) :: a(n,n)
369
- complex (qp), parameter :: i_ = complex (0 ,1 )
367
+ complex (qp), parameter :: i_ = cmplx (0 ,1 )
370
368
write (* ,* ) " test_trace_cqp"
371
369
a = 3 * eye(n) + 4 * eye(n)* i_ ! pythagorean triple
372
370
call check(abs (trace(a)) - 3 * 5.0_qp < qptol, &
@@ -442,4 +440,4 @@ pure recursive function catalan_number(n) result(value)
442
440
end if
443
441
end function
444
442
445
- end program
443
+ end program
0 commit comments