Skip to content

Commit 8471ded

Browse files
committed
Test for tokenize_flags (failing)
1 parent ab72aad commit 8471ded

File tree

1 file changed

+47
-11
lines changed

1 file changed

+47
-11
lines changed

test/fpm_test/test_compiler.f90

Lines changed: 47 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,8 @@ module test_compiler
33
use testsuite, only : new_unittest, unittest_t, error_t, test_failed, &
44
& check_string
55
use fpm_environment, only : OS_WINDOWS, OS_LINUX
6-
use fpm_compiler , only : compiler_t, new_compiler
6+
use fpm_compiler , only : compiler_t, new_compiler, tokenize_flags
7+
use fpm_strings , only : string_t
78
use fpm_command_line, only: get_fpm_env
89
implicit none
910
private
@@ -19,38 +20,73 @@ subroutine collect_compiler(testsuite)
1920
type(unittest_t), allocatable, intent(out) :: testsuite(:)
2021

2122
testsuite = [ &
22-
& new_unittest("check-fortran-source-runs", test_check_fortran_source_runs)]
23+
& new_unittest("check-fortran-source-runs", test_check_fortran_source_runs), &
24+
& new_unittest("tokenize-flags", test_tokenize_flags)]
2325

2426
end subroutine collect_compiler
25-
27+
2628
subroutine test_check_fortran_source_runs(error)
2729
!> Error handling
2830
type(error_t), allocatable, intent(out) :: error
29-
31+
3032
character(:), allocatable :: fc,cc,cxx
31-
32-
33+
34+
3335
type(compiler_t) :: compiler
3436

3537
!> Get default compiler
3638
fc = get_fpm_env("FC", default="gfortran")
3739
cc = get_fpm_env("CC", default=" ")
3840
cxx = get_fpm_env("CXX", default=" ")
39-
41+
4042
call new_compiler(compiler, fc, cc, cxx, echo=.false., verbose=.false.)
4143

4244
if (compiler%is_unknown()) then
4345
call test_failed(error, "Cannot initialize Fortran compiler")
4446
return
4547
end if
46-
48+
4749
!> Test fortran-source runs
48-
if (.not.compiler%check_fortran_source_runs("print *, 'Hello world!'; end")) then
50+
if (.not.compiler%check_fortran_source_runs("print *, 'Hello world!'; end")) then
4951
call test_failed(error, "Cannot run Fortran hello world")
5052
return
51-
end if
53+
end if
54+
55+
end subroutine test_check_fortran_source_runs
56+
57+
subroutine test_tokenize_flags(error)
58+
type(error_t), allocatable, intent(out) :: error
59+
60+
character(:), allocatable :: flags
61+
type(string_t), allocatable :: tokens(:)
62+
integer :: i
63+
64+
flags = '-I/path/to/include -I /test -I"/path/to/include with spaces" ' // &
65+
'-I "spaces here too" -L/path/to/lib -lmylib -O2 -g -Wall'
66+
call tokenize_flags(flags, tokens)
67+
68+
do i = 1, size(tokens)
69+
print *, "Tokens ", i, ": ", tokens(i)%s
70+
end do
71+
72+
if (tokens(1)%s /= '-I/path/to/include') then
73+
call test_failed(error, "Tokenization of flags failed: expected '-I/path/to/include'")
74+
return
75+
end if
76+
if (tokens(2)%s /= '-I/test') then
77+
call test_failed(error, "Tokenization of flags failed: expected '-I/test'")
78+
return
79+
end if
80+
if (tokens(3)%s /= '-I"/path/to/include with spaces"') then
81+
call test_failed(error, 'Tokenization of flags failed: expected -I"/path/to/include with spaces"')
82+
return
83+
end if
5284

53-
end subroutine test_check_fortran_source_runs
85+
if (size(tokens) /= 9) then
86+
call test_failed(error, "Tokenization of flags failed: expected 9 tokens")
87+
return
88+
end if
5489

90+
end subroutine test_tokenize_flags
5591

5692
end module test_compiler

0 commit comments

Comments
 (0)