28
28
module fpm_backend
29
29
30
30
use fpm_environment, only: run, get_os_type, OS_WINDOWS
31
- use fpm_filesystem, only: dirname, join_path, exists, mkdir, unix_path
31
+ use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir, unix_path
32
32
use fpm_model, only: fpm_model_t
33
33
use fpm_targets, only: build_target_t, build_target_ptr, FPM_TARGET_OBJECT, &
34
34
FPM_TARGET_C_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
@@ -48,7 +48,8 @@ subroutine build_package(targets,model)
48
48
49
49
integer :: i, j
50
50
type (build_target_ptr), allocatable :: queue(:)
51
- integer , allocatable :: schedule_ptr(:)
51
+ integer , allocatable :: schedule_ptr(:), stat(:)
52
+ logical :: build_failed, skip_current
52
53
53
54
! Need to make output directory for include (mod) files
54
55
if (.not. exists(join_path(model% output_directory,model% package_name))) then
@@ -65,17 +66,44 @@ subroutine build_package(targets,model)
65
66
! Construct build schedule queue
66
67
call schedule_targets(queue, schedule_ptr, targets)
67
68
69
+ ! Initialise build status flags
70
+ allocate (stat(size (queue)))
71
+ stat(:) = 0
72
+ build_failed = .false.
73
+
68
74
! Loop over parallel schedule regions
69
75
do i= 1 ,size (schedule_ptr)- 1
70
76
71
77
! Build targets in schedule region i
72
- ! $omp parallel do default(shared) schedule(dynamic,1)
78
+ ! $omp parallel do default(shared) private(skip_current) schedule(dynamic,1)
73
79
do j= schedule_ptr(i),(schedule_ptr(i+1 )- 1 )
74
80
75
- call build_target(model,queue(j)% ptr)
81
+ ! Check if build already failed
82
+ ! $omp atomic read
83
+ skip_current = build_failed
84
+
85
+ if (.not. skip_current) then
86
+ call build_target(model,queue(j)% ptr,stat(j))
87
+ end if
88
+
89
+ ! Set global flag if this target failed to build
90
+ if (stat(j) /= 0 ) then
91
+ ! $omp atomic write
92
+ build_failed = .true.
93
+ end if
76
94
77
95
end do
78
96
97
+ ! Check if this schedule region failed: exit with message if failed
98
+ if (build_failed) then
99
+ do j= 1 ,size (stat)
100
+ if (stat(j) /= 0 ) then
101
+ write (* ,* ) ' <ERROR> Compilation failed for object "' ,basename(queue(j)% ptr% output_file),' "'
102
+ end if
103
+ end do
104
+ stop 1
105
+ end if
106
+
79
107
end do
80
108
81
109
end subroutine build_package
@@ -223,9 +251,10 @@ end subroutine schedule_targets
223
251
! >
224
252
! > If successful, also caches the source file digest to disk.
225
253
! >
226
- subroutine build_target (model ,target )
254
+ subroutine build_target (model ,target , stat )
227
255
type (fpm_model_t), intent (in ) :: model
228
256
type (build_target_t), intent (in ), target :: target
257
+ integer , intent (out ) :: stat
229
258
230
259
integer :: ilib, fh
231
260
character (:), allocatable :: link_flags
@@ -238,32 +267,34 @@ subroutine build_target(model,target)
238
267
239
268
case (FPM_TARGET_OBJECT)
240
269
call run(model% fortran_compiler// " -c " // target % source% file_name // target % compile_flags &
241
- // " -o " // target % output_file)
270
+ // " -o " // target % output_file, echo = .true. , exitstat = stat )
242
271
243
272
case (FPM_TARGET_C_OBJECT)
244
273
call run(model% c_compiler// " -c " // target % source% file_name // target % compile_flags &
245
- // " -o " // target % output_file)
274
+ // " -o " // target % output_file, echo = .true. , exitstat = stat )
246
275
247
276
case (FPM_TARGET_EXECUTABLE)
248
277
249
278
call run(model% fortran_compiler// " " // target % compile_flags &
250
- // " " // target % link_flags// " -o " // target % output_file)
279
+ // " " // target % link_flags// " -o " // target % output_file, echo = .true. , exitstat = stat )
251
280
252
281
case (FPM_TARGET_ARCHIVE)
253
282
254
283
select case (get_os_type())
255
284
case (OS_WINDOWS)
256
285
call write_response_file(target % output_file// " .resp" ,target % link_objects)
257
- call run(model% archiver // target % output_file // " @" // target % output_file// " .resp" )
286
+ call run(model% archiver // target % output_file // " @" // target % output_file// " .resp" , &
287
+ echo= .true. , exitstat= stat)
258
288
259
289
case default
260
- call run(model% archiver // target % output_file // " " // string_cat(target % link_objects," " ))
290
+ call run(model% archiver // target % output_file // " " // string_cat(target % link_objects," " ), &
291
+ echo= .true. , exitstat= stat)
261
292
262
293
end select
263
294
264
295
end select
265
296
266
- if (allocated (target % source)) then
297
+ if (stat == 0 .and. allocated (target % source)) then
267
298
open (newunit= fh,file= target % output_file// ' .digest' ,status= ' unknown' )
268
299
write (fh,* ) target % source% digest
269
300
close (fh)
0 commit comments