Skip to content

Commit 086ae55

Browse files
committed
Update: backend to fail more gracefully for compilation errors
Removes fpm backtrace and lists target(s) that failed
1 parent 0d3611a commit 086ae55

File tree

2 files changed

+50
-13
lines changed

2 files changed

+50
-13
lines changed

src/fpm_backend.f90

Lines changed: 39 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@
2828
module fpm_backend
2929

3030
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
3232
use fpm_model, only: fpm_model_t
3333
use fpm_targets, only: build_target_t, build_target_ptr, &
3434
FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
@@ -49,7 +49,8 @@ subroutine build_package(targets,model)
4949

5050
integer :: i, j
5151
type(build_target_ptr), allocatable :: queue(:)
52-
integer, allocatable :: schedule_ptr(:)
52+
integer, allocatable :: schedule_ptr(:), stat(:)
53+
logical :: build_failed, skip_current
5354

5455
! Need to make output directory for include (mod) files
5556
if (.not.exists(join_path(model%output_directory,model%package_name))) then
@@ -66,17 +67,44 @@ subroutine build_package(targets,model)
6667
! Construct build schedule queue
6768
call schedule_targets(queue, schedule_ptr, targets)
6869

70+
! Initialise build status flags
71+
allocate(stat(size(queue)))
72+
stat(:) = 0
73+
build_failed = .false.
74+
6975
! Loop over parallel schedule regions
7076
do i=1,size(schedule_ptr)-1
7177

7278
! 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)
7480
do j=schedule_ptr(i),(schedule_ptr(i+1)-1)
7581

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
7795

7896
end do
7997

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+
80108
end do
81109

82110
end subroutine build_package
@@ -224,9 +252,10 @@ end subroutine schedule_targets
224252
!>
225253
!> If successful, also caches the source file digest to disk.
226254
!>
227-
subroutine build_target(model,target)
255+
subroutine build_target(model,target,stat)
228256
type(fpm_model_t), intent(in) :: model
229257
type(build_target_t), intent(in), target :: target
258+
integer, intent(out) :: stat
230259

231260
integer :: ilib, fh
232261
character(:), allocatable :: link_flags
@@ -239,19 +268,20 @@ subroutine build_target(model,target)
239268

240269
case (FPM_TARGET_OBJECT)
241270
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)
243272

244273
case (FPM_TARGET_EXECUTABLE)
245274

246275
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)
248277

249278
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)
251281

252282
end select
253283

254-
if (allocated(target%source)) then
284+
if (stat == 0 .and. allocated(target%source)) then
255285
open(newunit=fh,file=target%output_file//'.digest',status='unknown')
256286
write(fh,*) target%source%digest
257287
close(fh)

src/fpm_environment.f90

Lines changed: 11 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -125,9 +125,10 @@ logical function os_is_unix(os) result(unix)
125125
end function os_is_unix
126126

127127
!> echo command string and pass it to the system for execution
128-
subroutine run(cmd,echo)
128+
subroutine run(cmd,echo,exitstat)
129129
character(len=*), intent(in) :: cmd
130130
logical,intent(in),optional :: echo
131+
integer, intent(out),optional :: exitstat
131132
logical :: echo_local
132133
integer :: stat
133134

@@ -139,10 +140,16 @@ subroutine run(cmd,echo)
139140
if(echo_local) print *, '+ ', cmd
140141

141142
call execute_command_line(cmd, exitstat=stat)
142-
if (stat /= 0) then
143-
print *, 'Command failed'
144-
error stop
143+
144+
if (present(exitstat)) then
145+
exitstat = stat
146+
else
147+
if (stat /= 0) then
148+
print *, 'Command failed'
149+
error stop
150+
end if
145151
end if
152+
146153
end subroutine run
147154

148155
!> get named environment variable value. It it is blank or

0 commit comments

Comments
 (0)