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