1
1
! > Define tests for the `fpm_sources` module (module dependency checking)
2
2
module test_module_dependencies
3
3
use testsuite, only : new_unittest, unittest_t, error_t, test_failed
4
- use fpm_targets, only: targets_from_sources, resolve_module_dependencies
4
+ use fpm_targets, only: targets_from_sources, resolve_module_dependencies, &
5
+ resolve_target_linking
5
6
use fpm_model, only: fpm_model_t, srcfile_t, build_target_t, build_target_ptr, &
6
7
FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
7
8
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
8
9
FPM_UNIT_CHEADER, FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
9
10
FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST, &
10
11
FPM_TARGET_EXECUTABLE, FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE
11
- use fpm_strings, only: string_t
12
+ use fpm_strings, only: string_t, operator (. in .)
12
13
implicit none
13
14
private
14
15
@@ -71,14 +72,16 @@ subroutine test_library_module_use(error)
71
72
if (allocated (error)) then
72
73
return
73
74
end if
74
-
75
75
if (size (model% targets) /= 3 ) then
76
76
call test_failed(error,' Incorrect number of model%targets - expecting three' )
77
77
return
78
78
end if
79
79
80
+ call resolve_target_linking(model% targets)
81
+
80
82
call check_target(model% targets(1 )% ptr,type= FPM_TARGET_ARCHIVE,n_depends= 2 , &
81
- deps = [model% targets(2 ),model% targets(3 )],error= error)
83
+ deps = [model% targets(2 ),model% targets(3 )], &
84
+ links = model% targets(2 :3 ), error= error)
82
85
83
86
if (allocated (error)) return
84
87
@@ -146,8 +149,10 @@ subroutine test_scope(exe_scope,error)
146
149
return
147
150
end if
148
151
152
+ call resolve_target_linking(model% targets)
153
+
149
154
call check_target(model% targets(1 )% ptr,type= FPM_TARGET_ARCHIVE,n_depends= 1 , &
150
- deps= [model% targets(2 )],error= error)
155
+ deps= [model% targets(2 )],links = [model % targets( 2 )], error= error)
151
156
152
157
if (allocated (error)) return
153
158
@@ -162,7 +167,8 @@ subroutine test_scope(exe_scope,error)
162
167
if (allocated (error)) return
163
168
164
169
call check_target(model% targets(4 )% ptr,type= FPM_TARGET_EXECUTABLE,n_depends= 2 , &
165
- deps= [model% targets(1 ),model% targets(3 )],error= error)
170
+ deps= [model% targets(1 ),model% targets(3 )], &
171
+ links= [model% targets(3 )], error= error)
166
172
167
173
if (allocated (error)) return
168
174
@@ -202,20 +208,22 @@ subroutine test_program_with_module(error)
202
208
return
203
209
end if
204
210
211
+ call resolve_target_linking(model% targets)
212
+
205
213
call check_target(model% targets(1 )% ptr,type= FPM_TARGET_OBJECT,n_depends= 0 , &
206
214
source= sources(1 ),error= error)
207
215
208
216
if (allocated (error)) return
209
217
210
218
call check_target(model% targets(2 )% ptr,type= FPM_TARGET_EXECUTABLE,n_depends= 1 , &
211
- deps= [model% targets(1 )],error= error)
219
+ deps= [model% targets(1 )],links = [model % targets( 1 )], error= error)
212
220
213
221
if (allocated (error)) return
214
222
215
223
end subroutine test_program_with_module
216
224
217
225
218
- ! > Check program using a module in same directory
226
+ ! > Check program using modules in same directory
219
227
subroutine test_program_own_module_use (error )
220
228
221
229
! > Error handling
@@ -233,21 +241,25 @@ subroutine test_scope(exe_scope,error)
233
241
integer , intent (in ) :: exe_scope
234
242
type (error_t), allocatable , intent (out ) :: error
235
243
236
- type (srcfile_t) :: sources(2 )
244
+ type (srcfile_t) :: sources(3 )
237
245
type (fpm_model_t) :: model
238
246
character (:), allocatable :: scope_str
239
247
240
248
model% output_directory = ' '
241
249
242
250
scope_str = merge (' FPM_SCOPE_APP ' ,' FPM_SCOPE_TEST' ,exe_scope== FPM_SCOPE_APP)// ' - '
243
251
244
- sources(1 ) = new_test_source(FPM_UNIT_MODULE,file_name= " app/app_mod .f90" , &
252
+ sources(1 ) = new_test_source(FPM_UNIT_MODULE,file_name= " app/app_mod1 .f90" , &
245
253
scope = exe_scope, &
246
- provides= [string_t(' app_mod ' )])
254
+ provides= [string_t(' app_mod1 ' )])
247
255
248
- sources(2 ) = new_test_source(FPM_UNIT_PROGRAM,file_name= " app/my_program.f90" , &
256
+ sources(2 ) = new_test_source(FPM_UNIT_MODULE,file_name= " app/app_mod2.f90" , &
257
+ scope = exe_scope, &
258
+ provides= [string_t(' app_mod2' )],uses= [string_t(' app_mod1' )])
259
+
260
+ sources(3 ) = new_test_source(FPM_UNIT_PROGRAM,file_name= " app/my_program.f90" , &
249
261
scope= exe_scope, &
250
- uses= [string_t(' app_mod ' )])
262
+ uses= [string_t(' app_mod2 ' )])
251
263
252
264
call targets_from_sources(model,sources)
253
265
call resolve_module_dependencies(model% targets,error)
@@ -256,11 +268,12 @@ subroutine test_scope(exe_scope,error)
256
268
return
257
269
end if
258
270
259
- if (size (model% targets) /= 3 ) then
271
+ if (size (model% targets) /= 4 ) then
260
272
call test_failed(error,scope_str// ' Incorrect number of model%targets - expecting three' )
261
273
return
262
274
end if
263
275
276
+ call resolve_target_linking(model% targets)
264
277
265
278
call check_target(model% targets(1 )% ptr,type= FPM_TARGET_OBJECT,n_depends= 0 , &
266
279
source= sources(1 ),error= error)
@@ -272,11 +285,16 @@ subroutine test_scope(exe_scope,error)
272
285
273
286
if (allocated (error)) return
274
287
275
- call check_target(model% targets(3 )% ptr,type= FPM_TARGET_EXECUTABLE,n_depends= 1 , &
276
- deps= [model% targets(2 )],error= error)
288
+ call check_target(model% targets(3 )% ptr,type= FPM_TARGET_OBJECT,n_depends= 1 , &
289
+ source= sources(3 ),deps= [model% targets(2 )],error= error)
290
+
291
+ if (allocated (error)) return
292
+
293
+ call check_target(model% targets(4 )% ptr,type= FPM_TARGET_EXECUTABLE,n_depends= 1 , &
294
+ deps= [model% targets(3 )],links= model% targets(1 :3 ), error= error)
277
295
278
296
if (allocated (error)) return
279
-
297
+
280
298
end subroutine test_scope
281
299
end subroutine test_program_own_module_use
282
300
@@ -414,12 +432,13 @@ end function new_test_source
414
432
415
433
416
434
! > Helper to check an expected output target
417
- subroutine check_target (target ,type ,n_depends ,deps ,source ,error )
435
+ subroutine check_target (target ,type ,n_depends ,deps ,links , source ,error )
418
436
type (build_target_t), intent (in ) :: target
419
437
integer , intent (in ) :: type
420
438
integer , intent (in ) :: n_depends
421
439
type (srcfile_t), intent (in ), optional :: source
422
440
type (build_target_ptr), intent (in ), optional :: deps(:)
441
+ type (build_target_ptr), intent (in ), optional :: links(:)
423
442
type (error_t), intent (out ), allocatable :: error
424
443
425
444
integer :: i
@@ -448,6 +467,34 @@ subroutine check_target(target,type,n_depends,deps,source,error)
448
467
449
468
end if
450
469
470
+ if (present (links)) then
471
+
472
+ do i= 1 ,size (links)
473
+
474
+ if (.not. (links(i)% ptr% output_file .in . target % link_objects)) then
475
+ call test_failed(error,' Missing object (' // links(i)% ptr% output_file// &
476
+ ' ) for executable "' // target % output_file// ' "' )
477
+ return
478
+ end if
479
+
480
+ end do
481
+
482
+ if (size (links) > size (target % link_objects)) then
483
+
484
+ call test_failed(error,' There are missing link objects for target "' &
485
+ // target % output_file// ' "' )
486
+ return
487
+
488
+ elseif (size (links) < size (target % link_objects)) then
489
+
490
+ call test_failed(error,' There are more link objects than expected for target "' &
491
+ // target % output_file// ' "' )
492
+ return
493
+
494
+ end if
495
+
496
+ end if
497
+
451
498
if (present (source)) then
452
499
453
500
if (allocated (target % source)) then
0 commit comments