Skip to content

Commit 39bb56c

Browse files
committed
test for standard conformance
also one quick fix: complex => cmplx note that the current code does not compile Intel compiler: /tmp/stdlib/build/src/stdlib_experimental_linalg_diag.f90(7): error #6645: The name of the module procedure conflicts with a name in the encompassing scoping unit. [DIAG_RSP] function diag_rsp(v) result(res) GNU compiler /tmp/stdlib/src/tests/optval/test_optval.f90:252:15: 252 | z = optval(x, [2.0_qp, -2.0_qp]) | 1 Error: ‘x’ at (1) is an array and OPTIONAL; IF IT IS MISSING, it cannot be the actual argument of an ELEMENTAL procedure unless there is a non-optional argument with the same rank (12.4.1.5) [-Werror=pedantic]
1 parent 0ecaed5 commit 39bb56c

File tree

2 files changed

+25
-11
lines changed

2 files changed

+25
-11
lines changed

CMakeLists.txt

Lines changed: 15 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,8 +7,22 @@ include(${CMAKE_SOURCE_DIR}/cmake/stdlib.cmake)
77
# --- compiler options
88
if(CMAKE_Fortran_COMPILER_ID STREQUAL GNU)
99
add_compile_options(-fimplicit-none)
10+
add_compile_options(-ffree-line-length-132)
11+
add_compile_options(-Wall)
12+
add_compile_options(-Wextra)
13+
add_compile_options(-Wimplicit-procedure)
14+
add_compile_options(-Wconversion-extra)
15+
add_compile_options(-std=f2018)
16+
add_compile_options(-pedantic-errors)
17+
add_compile_options(-fallow-invalid-boz) # ToDo: hack for invalid code
1018
elseif(CMAKE_Fortran_COMPILER_ID STREQUAL Intel)
11-
add_compile_options(-warn declarations)
19+
add_compile_options(-warn declarations,general,usage,interfaces,unused)
20+
add_compile_options(-standard-semantics)
21+
if(CMAKE_Fortran_COMPILER_VERSION VERSION_LESS 18.0)
22+
add_compile_options(-stand f15)
23+
else()
24+
add_compile_options(-stand f18)
25+
endif()
1226
elseif(CMAKE_Fortran_COMPILER_ID STREQUAL PGI)
1327
add_compile_options(-Mdclchk)
1428
endif()

src/tests/linalg/test_linalg.f90

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -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
@@ -153,7 +153,7 @@ subroutine test_diag_rqp
153153
subroutine test_diag_csp
154154
integer, parameter :: n = 3
155155
complex(sp) :: v(n), a(n,n), b(n,n)
156-
complex(sp), parameter :: i_ = complex(0,1)
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)])
@@ -170,7 +170,7 @@ subroutine test_diag_csp
170170
subroutine test_diag_cdp
171171
integer, parameter :: n = 3
172172
complex(dp) :: v(n), a(n,n), b(n,n)
173-
complex(dp), parameter :: i_ = complex(0,1)
173+
complex(dp), parameter :: i_ = cmplx(0,1)
174174
integer :: i,j
175175
write(*,*) "test_diag_cdp"
176176
a = diag([i_],-2) + diag([i_],2)
@@ -181,7 +181,7 @@ subroutine test_diag_cdp
181181
subroutine test_diag_cqp
182182
integer, parameter :: n = 3
183183
complex(qp) :: v(n), a(n,n), b(n,n)
184-
complex(qp), parameter :: i_ = complex(0,1)
184+
complex(qp), parameter :: i_ = cmplx(0,1)
185185
integer :: i,j
186186
write(*,*) "test_diag_cqp"
187187
a = diag([i_,i_],-1) + diag([i_,i_],1)
@@ -333,7 +333,7 @@ subroutine test_trace_csp
333333
integer, parameter :: n = 5
334334
real(sp) :: re(n,n), im(n,n)
335335
complex(sp) :: a(n,n), b(n,n)
336-
complex(sp), parameter :: i_ = complex(0,1)
336+
complex(sp), parameter :: i_ = cmplx(0,1)
337337
write(*,*) "test_trace_csp"
338338

339339
call random_number(re)
@@ -352,12 +352,12 @@ subroutine test_trace_csp
352352
subroutine test_trace_cdp
353353
integer, parameter :: n = 3
354354
complex(dp) :: a(n,n), ans
355-
complex(dp), parameter :: i_ = complex(0,1)
355+
complex(dp), parameter :: i_ = cmplx(0,1)
356356
integer :: j
357357
write(*,*) "test_trace_cdp"
358358

359359
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
360+
ans = cmplx(15,15) !(1 + 5 + 9) + (9 + 5 + 1)i
361361

362362
call check(abs(trace(a) - ans) < dptol, &
363363
msg="abs(trace(a) - ans) < dptol failed.",warn=warn)
@@ -366,7 +366,7 @@ subroutine test_trace_cdp
366366
subroutine test_trace_cqp
367367
integer, parameter :: n = 3
368368
complex(qp) :: a(n,n)
369-
complex(qp), parameter :: i_ = complex(0,1)
369+
complex(qp), parameter :: i_ = cmplx(0,1)
370370
write(*,*) "test_trace_cqp"
371371
a = 3*eye(n) + 4*eye(n)*i_ ! pythagorean triple
372372
call check(abs(trace(a)) - 3*5.0_qp < qptol, &
@@ -442,4 +442,4 @@ pure recursive function catalan_number(n) result(value)
442442
end if
443443
end function
444444

445-
end program
445+
end program

0 commit comments

Comments
 (0)