Skip to content

Commit e04de5a

Browse files
committed
Add: test suite for module dependency resolution logic
1 parent 70f0039 commit e04de5a

File tree

2 files changed

+366
-1
lines changed

2 files changed

+366
-1
lines changed

fpm/test/main.f90

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@ program fpm_testing
66
use test_toml, only : collect_toml
77
use test_manifest, only : collect_manifest
88
use test_source_parsing, only : collect_source_parsing
9+
use test_module_dependencies, only : collect_module_dependencies
910
implicit none
1011
integer :: stat, is
1112
character(len=:), allocatable :: suite_name, test_name
@@ -17,7 +18,8 @@ program fpm_testing
1718
testsuite = [ &
1819
& new_testsuite("fpm_toml", collect_toml), &
1920
& new_testsuite("fpm_manifest", collect_manifest), &
20-
& new_testsuite("fpm_source_parsing", collect_source_parsing) &
21+
& new_testsuite("fpm_source_parsing", collect_source_parsing), &
22+
& new_testsuite("fpm_module_dependencies", collect_module_dependencies) &
2123
& ]
2224

2325
call get_argument(1, suite_name)
Lines changed: 363 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,363 @@
1+
!> Define tests for the `fpm_sources` module (module dependency checking)
2+
module test_module_dependencies
3+
use testsuite, only : new_unittest, unittest_t, error_t, test_failed
4+
use fpm_sources, only: resolve_module_dependencies
5+
use fpm_model, only: srcfile_t, srcfile_ptr, &
6+
FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
7+
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
8+
FPM_UNIT_CHEADER, FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
9+
FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST
10+
use fpm_strings, only: string_t
11+
implicit none
12+
private
13+
14+
public :: collect_module_dependencies
15+
16+
interface operator(.in.)
17+
module procedure srcfile_in
18+
end interface
19+
20+
contains
21+
22+
23+
!> Collect all exported unit tests
24+
subroutine collect_module_dependencies(testsuite)
25+
26+
!> Collection of tests
27+
type(unittest_t), allocatable, intent(out) :: testsuite(:)
28+
29+
testsuite = [ &
30+
& new_unittest("library-module-use", test_library_module_use), &
31+
& new_unittest("program-module-use", test_program_module_use), &
32+
& new_unittest("program-with-module", test_program_with_module), &
33+
& new_unittest("program-own-module-use", test_program_own_module_use), &
34+
& new_unittest("missing-library-use", &
35+
test_missing_library_use, should_fail=.true.), &
36+
& new_unittest("missing-program-use", &
37+
test_missing_program_use, should_fail=.true.), &
38+
& new_unittest("invalid-library-use", &
39+
test_invalid_library_use, should_fail=.true.), &
40+
& new_unittest("invalid-own-module-use", &
41+
test_invalid_own_module_use, should_fail=.true.) &
42+
]
43+
44+
end subroutine collect_module_dependencies
45+
46+
47+
!> Check library module using another library module
48+
subroutine test_library_module_use(error)
49+
50+
!> Error handling
51+
type(error_t), allocatable, intent(out) :: error
52+
53+
type(srcfile_t) :: sources(2)
54+
55+
sources(1) = new_test_module(file_name="src/my_mod_1.f90", &
56+
scope = FPM_SCOPE_LIB, &
57+
provides=[string_t('my_mod_1')])
58+
59+
sources(2) = new_test_module(file_name="src/my_mod_2.f90", &
60+
scope = FPM_SCOPE_LIB, &
61+
provides=[string_t('my_mod_2')], &
62+
uses=[string_t('my_mod_1')])
63+
64+
call resolve_module_dependencies(sources,error)
65+
66+
if (allocated(error)) then
67+
return
68+
end if
69+
70+
if (size(sources(1)%file_dependencies)>0) then
71+
call test_failed(error,'Incorrect number of file_dependencies - expecting zero')
72+
return
73+
end if
74+
75+
if (size(sources(2)%file_dependencies) /= 1) then
76+
call test_failed(error,'Incorrect number of file_dependencies - expecting one')
77+
return
78+
end if
79+
80+
if (.not.(sources(1) .in. sources(2)%file_dependencies)) then
81+
call test_failed(error,'Missing file in file_dependencies')
82+
return
83+
end if
84+
85+
end subroutine test_library_module_use
86+
87+
88+
!> Check program using a library module
89+
subroutine test_program_module_use(error)
90+
91+
!> Error handling
92+
type(error_t), allocatable, intent(out) :: error
93+
94+
integer :: i
95+
type(srcfile_t) :: sources(3)
96+
97+
sources(1) = new_test_module(file_name="src/my_mod_1.f90", &
98+
scope = FPM_SCOPE_LIB, &
99+
provides=[string_t('my_mod_1')])
100+
101+
sources(2) = new_test_program(file_name="app/my_program.f90", &
102+
scope=FPM_SCOPE_APP, &
103+
uses=[string_t('my_mod_1')])
104+
105+
sources(3) = new_test_program(file_name="test/my_test.f90", &
106+
scope=FPM_SCOPE_TEST, &
107+
uses=[string_t('my_mod_1')])
108+
109+
call resolve_module_dependencies(sources,error)
110+
111+
if (allocated(error)) then
112+
return
113+
end if
114+
115+
if (size(sources(1)%file_dependencies)>0) then
116+
call test_failed(error,'Incorrect number of file_dependencies - expecting zero')
117+
return
118+
end if
119+
120+
do i=2,3
121+
122+
if (size(sources(i)%file_dependencies) /= 1) then
123+
call test_failed(error,'Incorrect number of file_dependencies - expecting one')
124+
return
125+
end if
126+
127+
if (.not.(sources(1) .in. sources(i)%file_dependencies)) then
128+
call test_failed(error,'Missing file in file_dependencies')
129+
return
130+
end if
131+
132+
end do
133+
134+
end subroutine test_program_module_use
135+
136+
137+
!> Check program with module in single source file
138+
!> (Resulting source object should not include itself as a file dependency)
139+
subroutine test_program_with_module(error)
140+
141+
!> Error handling
142+
type(error_t), allocatable, intent(out) :: error
143+
144+
integer :: i
145+
type(srcfile_t) :: sources(1)
146+
147+
sources(1) = new_test_module(file_name="app/my_program.f90", &
148+
scope = FPM_SCOPE_APP, &
149+
provides=[string_t('app_mod')], &
150+
uses=[string_t('app_mod')])
151+
152+
call resolve_module_dependencies(sources,error)
153+
154+
if (allocated(error)) then
155+
return
156+
end if
157+
158+
if (size(sources(1)%file_dependencies)>0) then
159+
call test_failed(error,'Incorrect number of file_dependencies - expecting zero')
160+
return
161+
end if
162+
163+
end subroutine test_program_with_module
164+
165+
166+
!> Check program using a module in same directory
167+
subroutine test_program_own_module_use(error)
168+
169+
!> Error handling
170+
type(error_t), allocatable, intent(out) :: error
171+
172+
type(srcfile_t) :: sources(2)
173+
174+
sources(1) = new_test_module(file_name="app/app_mod.f90", &
175+
scope = FPM_SCOPE_APP, &
176+
provides=[string_t('app_mod')])
177+
178+
sources(2) = new_test_program(file_name="app/my_program.f90", &
179+
scope=FPM_SCOPE_APP, &
180+
uses=[string_t('app_mod')])
181+
182+
call resolve_module_dependencies(sources,error)
183+
184+
if (allocated(error)) then
185+
return
186+
end if
187+
188+
if (size(sources(1)%file_dependencies)>0) then
189+
call test_failed(error,'Incorrect number of file_dependencies - expecting zero')
190+
return
191+
end if
192+
193+
if (size(sources(2)%file_dependencies) /= 1) then
194+
call test_failed(error,'Incorrect number of file_dependencies - expecting one')
195+
return
196+
end if
197+
198+
if (.not.(sources(1) .in. sources(2)%file_dependencies)) then
199+
call test_failed(error,'Missing file in file_dependencies')
200+
return
201+
end if
202+
203+
end subroutine test_program_own_module_use
204+
205+
206+
!> Check missing library module dependency
207+
subroutine test_missing_library_use(error)
208+
209+
!> Error handling
210+
type(error_t), allocatable, intent(out) :: error
211+
212+
type(srcfile_t) :: sources(2)
213+
214+
sources(1) = new_test_module(file_name="src/my_mod_1.f90", &
215+
scope = FPM_SCOPE_LIB, &
216+
provides=[string_t('my_mod_1')])
217+
218+
sources(2) = new_test_module(file_name="src/my_mod_2.f90", &
219+
scope = FPM_SCOPE_LIB, &
220+
provides=[string_t('my_mod_2')], &
221+
uses=[string_t('my_mod_3')])
222+
223+
call resolve_module_dependencies(sources,error)
224+
225+
end subroutine test_missing_library_use
226+
227+
228+
!> Check missing program module dependency
229+
subroutine test_missing_program_use(error)
230+
231+
!> Error handling
232+
type(error_t), allocatable, intent(out) :: error
233+
234+
type(srcfile_t) :: sources(2)
235+
236+
sources(1) = new_test_module(file_name="src/my_mod_1.f90", &
237+
scope = FPM_SCOPE_LIB, &
238+
provides=[string_t('my_mod_1')])
239+
240+
sources(2) = new_test_program(file_name="app/my_program.f90", &
241+
scope=FPM_SCOPE_APP, &
242+
uses=[string_t('my_mod_2')])
243+
244+
call resolve_module_dependencies(sources,error)
245+
246+
end subroutine test_missing_program_use
247+
248+
249+
!> Check library module using a non-library module
250+
subroutine test_invalid_library_use(error)
251+
252+
!> Error handling
253+
type(error_t), allocatable, intent(out) :: error
254+
255+
type(srcfile_t) :: sources(2)
256+
257+
sources(1) = new_test_module(file_name="app/app_mod.f90", &
258+
scope = FPM_SCOPE_APP, &
259+
provides=[string_t('app_mod')])
260+
261+
sources(2) = new_test_module(file_name="src/my_mod.f90", &
262+
scope = FPM_SCOPE_LIB, &
263+
provides=[string_t('my_mod')], &
264+
uses=[string_t('app_mod')])
265+
266+
call resolve_module_dependencies(sources,error)
267+
268+
end subroutine test_invalid_library_use
269+
270+
271+
!> Check program using a non-library module in a different directory
272+
subroutine test_invalid_own_module_use(error)
273+
274+
!> Error handling
275+
type(error_t), allocatable, intent(out) :: error
276+
277+
type(srcfile_t) :: sources(2)
278+
279+
sources(1) = new_test_module(file_name="app/subdir/app_mod.f90", &
280+
scope = FPM_SCOPE_APP, &
281+
provides=[string_t('app_mod')])
282+
283+
sources(2) = new_test_program(file_name="app/my_program.f90", &
284+
scope=FPM_SCOPE_APP, &
285+
uses=[string_t('app_mod')])
286+
287+
call resolve_module_dependencies(sources,error)
288+
289+
end subroutine test_invalid_own_module_use
290+
291+
292+
!> Helper to create a new srcfile_t for a module
293+
function new_test_module(file_name, scope, uses, provides) result(src)
294+
character(*), intent(in) :: file_name
295+
integer, intent(in) :: scope
296+
type(string_t), intent(in), optional :: uses(:)
297+
type(string_t), intent(in), optional :: provides(:)
298+
type(srcfile_t) :: src
299+
300+
src%file_name = file_name
301+
src%unit_scope = scope
302+
src%unit_type = FPM_UNIT_MODULE
303+
304+
if (present(provides)) then
305+
src%modules_provided = provides
306+
else
307+
allocate(src%modules_provided(0))
308+
end if
309+
310+
if (present(uses)) then
311+
src%modules_used = uses
312+
else
313+
allocate(src%modules_used(0))
314+
end if
315+
316+
allocate(src%include_dependencies(0))
317+
318+
end function new_test_module
319+
320+
321+
!> Helper to create a new srcfile_t for a program
322+
function new_test_program(file_name, scope, uses) result(src)
323+
character(*), intent(in) :: file_name
324+
integer, intent(in) :: scope
325+
type(string_t), intent(in), optional :: uses(:)
326+
type(srcfile_t) :: src
327+
328+
src%file_name = file_name
329+
src%unit_scope = scope
330+
src%unit_type = FPM_UNIT_PROGRAM
331+
332+
if (present(uses)) then
333+
src%modules_used = uses
334+
else
335+
allocate(src%modules_used(0))
336+
end if
337+
338+
allocate(src%modules_provided(0))
339+
allocate(src%include_dependencies(0))
340+
341+
end function new_test_program
342+
343+
344+
!> Helper to check if a srcfile is in a list of srcfile_ptr
345+
logical function srcfile_in(needle,haystack)
346+
type(srcfile_t), intent(in), target :: needle
347+
type(srcfile_ptr), intent(in) :: haystack(:)
348+
349+
integer :: i
350+
351+
srcfile_in = .false.
352+
do i=1,size(haystack)
353+
354+
if (associated(haystack(i)%ptr,needle)) then
355+
srcfile_in = .true.
356+
return
357+
end if
358+
359+
end do
360+
361+
end function srcfile_in
362+
363+
end module test_module_dependencies

0 commit comments

Comments
 (0)