Skip to content

Commit 0411780

Browse files
authored
Merge pull request #491 from LKedward/backend-grace
Catch execute_command_line errors and print useful messages
2 parents d693d68 + faae6a4 commit 0411780

File tree

3 files changed

+69
-17
lines changed

3 files changed

+69
-17
lines changed

src/fpm.f90

Lines changed: 16 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -298,6 +298,7 @@ subroutine cmd_run(settings,test)
298298
type(build_target_t), pointer :: exe_target
299299
type(srcfile_t), pointer :: exe_source
300300
integer :: run_scope
301+
integer, allocatable :: stat(:)
301302
character(len=:),allocatable :: line
302303
logical :: toomany
303304

@@ -418,18 +419,31 @@ subroutine cmd_run(settings,test)
418419
call compact_list()
419420
else
420421

422+
allocate(stat(size(executables)))
421423
do i=1,size(executables)
422424
if (exists(executables(i)%s)) then
423425
if(settings%runner .ne. ' ')then
424-
call run(settings%runner//' '//executables(i)%s//" "//settings%args,echo=settings%verbose)
426+
call run(settings%runner//' '//executables(i)%s//" "//settings%args, &
427+
echo=settings%verbose, exitstat=stat(i))
425428
else
426-
call run(executables(i)%s//" "//settings%args,echo=settings%verbose)
429+
call run(executables(i)%s//" "//settings%args,echo=settings%verbose, &
430+
exitstat=stat(i))
427431
endif
428432
else
429433
write(stderr,*)'fpm::run<ERROR>',executables(i)%s,' not found'
430434
stop 1
431435
end if
432436
end do
437+
438+
if (any(stat /= 0)) then
439+
do i=1,size(stat)
440+
if (stat(i) /= 0) then
441+
write(*,*) '<ERROR> Execution failed for "',basename(executables(i)%s),'"'
442+
end if
443+
end do
444+
stop 1
445+
end if
446+
433447
endif
434448
contains
435449
subroutine compact_list_all()

src/fpm_backend.f90

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

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

4949
integer :: i, j
5050
type(build_target_ptr), allocatable :: queue(:)
51-
integer, allocatable :: schedule_ptr(:)
51+
integer, allocatable :: schedule_ptr(:), stat(:)
52+
logical :: build_failed, skip_current
5253

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

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

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

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
7694

7795
end do
7896

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

81109
end subroutine build_package
@@ -223,9 +251,10 @@ end subroutine schedule_targets
223251
!>
224252
!> If successful, also caches the source file digest to disk.
225253
!>
226-
subroutine build_target(model,target)
254+
subroutine build_target(model,target,stat)
227255
type(fpm_model_t), intent(in) :: model
228256
type(build_target_t), intent(in), target :: target
257+
integer, intent(out) :: stat
229258

230259
integer :: ilib, fh
231260
character(:), allocatable :: link_flags
@@ -238,32 +267,34 @@ subroutine build_target(model,target)
238267

239268
case (FPM_TARGET_OBJECT)
240269
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)
242271

243272
case (FPM_TARGET_C_OBJECT)
244273
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)
246275

247276
case (FPM_TARGET_EXECUTABLE)
248277

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

252281
case (FPM_TARGET_ARCHIVE)
253282

254283
select case (get_os_type())
255284
case (OS_WINDOWS)
256285
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)
258288

259289
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)
261292

262293
end select
263294

264295
end select
265296

266-
if (allocated(target%source)) then
297+
if (stat == 0 .and. allocated(target%source)) then
267298
open(newunit=fh,file=target%output_file//'.digest',status='unknown')
268299
write(fh,*) target%source%digest
269300
close(fh)

src/fpm_environment.f90

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

139139
!> echo command string and pass it to the system for execution
140-
subroutine run(cmd,echo)
140+
subroutine run(cmd,echo,exitstat)
141141
character(len=*), intent(in) :: cmd
142142
logical,intent(in),optional :: echo
143+
integer, intent(out),optional :: exitstat
143144
logical :: echo_local
144145
integer :: stat
145146

@@ -151,10 +152,16 @@ subroutine run(cmd,echo)
151152
if(echo_local) print *, '+ ', cmd
152153

153154
call execute_command_line(cmd, exitstat=stat)
154-
if (stat /= 0) then
155-
print *, 'Command failed'
156-
error stop
155+
156+
if (present(exitstat)) then
157+
exitstat = stat
158+
else
159+
if (stat /= 0) then
160+
print *, 'Command failed'
161+
error stop
162+
end if
157163
end if
164+
158165
end subroutine run
159166

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

0 commit comments

Comments
 (0)