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