From 086ae55dfa09c1924d2b54bc88ddb1827f9dcfa7 Mon Sep 17 00:00:00 2001 From: LKedward Date: Thu, 15 Apr 2021 19:06:03 +0100 Subject: Update: backend to fail more gracefully for compilation errors Removes fpm backtrace and lists target(s) that failed --- src/fpm_backend.f90 | 48 +++++++++++++++++++++++++++++++++++++++--------- src/fpm_environment.f90 | 15 +++++++++++---- 2 files changed, 50 insertions(+), 13 deletions(-) (limited to 'src') diff --git a/src/fpm_backend.f90 b/src/fpm_backend.f90 index 74cef61..799b7a6 100644 --- a/src/fpm_backend.f90 +++ b/src/fpm_backend.f90 @@ -28,7 +28,7 @@ module fpm_backend use fpm_environment, only: run -use fpm_filesystem, only: dirname, join_path, exists, mkdir +use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir use fpm_model, only: fpm_model_t use fpm_targets, only: build_target_t, build_target_ptr, & FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE @@ -49,7 +49,8 @@ subroutine build_package(targets,model) integer :: i, j type(build_target_ptr), allocatable :: queue(:) - integer, allocatable :: schedule_ptr(:) + integer, allocatable :: schedule_ptr(:), stat(:) + logical :: build_failed, skip_current ! Need to make output directory for include (mod) files if (.not.exists(join_path(model%output_directory,model%package_name))) then @@ -66,17 +67,44 @@ subroutine build_package(targets,model) ! Construct build schedule queue call schedule_targets(queue, schedule_ptr, targets) + ! Initialise build status flags + allocate(stat(size(queue))) + stat(:) = 0 + build_failed = .false. + ! Loop over parallel schedule regions do i=1,size(schedule_ptr)-1 ! Build targets in schedule region i - !$omp parallel do default(shared) schedule(dynamic,1) + !$omp parallel do default(shared) private(skip_current) schedule(dynamic,1) do j=schedule_ptr(i),(schedule_ptr(i+1)-1) - call build_target(model,queue(j)%ptr) + ! Check if build already failed + !$omp atomic read + skip_current = build_failed + + if (.not.skip_current) then + call build_target(model,queue(j)%ptr,stat(j)) + end if + + ! Set global flag if this target failed to build + if (stat(j) /= 0) then + !$omp atomic write + build_failed = .true. + end if end do + ! Check if this schedule region failed: exit with message if failed + if (build_failed) then + do j=1,size(stat) + if (stat(j) /= 0) then + write(*,*) ' Compilation failed for object "',basename(queue(j)%ptr%output_file),'"' + end if + end do + stop 1 + end if + end do end subroutine build_package @@ -224,9 +252,10 @@ end subroutine schedule_targets !> !> If successful, also caches the source file digest to disk. !> -subroutine build_target(model,target) +subroutine build_target(model,target,stat) type(fpm_model_t), intent(in) :: model type(build_target_t), intent(in), target :: target + integer, intent(out) :: stat integer :: ilib, fh character(:), allocatable :: link_flags @@ -239,19 +268,20 @@ subroutine build_target(model,target) case (FPM_TARGET_OBJECT) call run(model%fortran_compiler//" -c " // target%source%file_name // target%compile_flags & - // " -o " // target%output_file) + // " -o " // target%output_file, echo=.true., exitstat=stat) case (FPM_TARGET_EXECUTABLE) call run(model%fortran_compiler// " " // target%compile_flags & - //" "//target%link_flags// " -o " // target%output_file) + //" "//target%link_flags// " -o " // target%output_file, echo=.true., exitstat=stat) case (FPM_TARGET_ARCHIVE) - call run("ar -rs " // target%output_file // " " // string_cat(target%link_objects," ")) + call run("ar -rs " // target%output_file // " " // string_cat(target%link_objects," "), & + echo=.true., exitstat=stat) end select - if (allocated(target%source)) then + if (stat == 0 .and. allocated(target%source)) then open(newunit=fh,file=target%output_file//'.digest',status='unknown') write(fh,*) target%source%digest close(fh) diff --git a/src/fpm_environment.f90 b/src/fpm_environment.f90 index 0408ec4..982380d 100644 --- a/src/fpm_environment.f90 +++ b/src/fpm_environment.f90 @@ -125,9 +125,10 @@ contains end function os_is_unix !> echo command string and pass it to the system for execution - subroutine run(cmd,echo) + subroutine run(cmd,echo,exitstat) character(len=*), intent(in) :: cmd logical,intent(in),optional :: echo + integer, intent(out),optional :: exitstat logical :: echo_local integer :: stat @@ -139,10 +140,16 @@ contains if(echo_local) print *, '+ ', cmd call execute_command_line(cmd, exitstat=stat) - if (stat /= 0) then - print *, 'Command failed' - error stop + + if (present(exitstat)) then + exitstat = stat + else + if (stat /= 0) then + print *, 'Command failed' + error stop + end if end if + end subroutine run !> get named environment variable value. It it is blank or -- cgit v1.2.3 From bb95f17cc2fc99603e0cd2f17ae4f9cda16faf3c Mon Sep 17 00:00:00 2001 From: LKedward Date: Sat, 5 Jun 2021 14:46:31 +0100 Subject: Add: graceful failure for running apps & tests Fixes #485 --- src/fpm.f90 | 18 ++++++++++++++++-- 1 file changed, 16 insertions(+), 2 deletions(-) (limited to 'src') diff --git a/src/fpm.f90 b/src/fpm.f90 index 5854cfb..401136b 100644 --- a/src/fpm.f90 +++ b/src/fpm.f90 @@ -297,6 +297,7 @@ subroutine cmd_run(settings,test) type(build_target_t), pointer :: exe_target type(srcfile_t), pointer :: exe_source integer :: run_scope + integer, allocatable :: stat(:) character(len=:),allocatable :: line logical :: toomany @@ -417,18 +418,31 @@ subroutine cmd_run(settings,test) call compact_list() else + allocate(stat(size(executables))) do i=1,size(executables) if (exists(executables(i)%s)) then if(settings%runner .ne. ' ')then - call run(settings%runner//' '//executables(i)%s//" "//settings%args,echo=settings%verbose) + call run(settings%runner//' '//executables(i)%s//" "//settings%args, & + echo=settings%verbose, exitstat=stat(i)) else - call run(executables(i)%s//" "//settings%args,echo=settings%verbose) + call run(executables(i)%s//" "//settings%args,echo=settings%verbose, & + exitstat=stat(i)) endif else write(stderr,*)'fpm::run',executables(i)%s,' not found' stop 1 end if end do + + if (any(stat /= 0)) then + do i=1,size(stat) + if (stat(i) /= 0) then + write(*,*) ' Execution failed for "',basename(executables(i)%s),'"' + end if + end do + stop 1 + end if + endif contains subroutine compact_list_all() -- cgit v1.2.3 From faae6a41552b020b683bc936a7dd5ee1723b2b0d Mon Sep 17 00:00:00 2001 From: LKedward Date: Sat, 5 Jun 2021 14:58:26 +0100 Subject: Add: missing exitstat to C targets --- src/fpm_backend.f90 | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) (limited to 'src') diff --git a/src/fpm_backend.f90 b/src/fpm_backend.f90 index bdec3af..8628ec4 100644 --- a/src/fpm_backend.f90 +++ b/src/fpm_backend.f90 @@ -271,7 +271,7 @@ subroutine build_target(model,target,stat) case (FPM_TARGET_C_OBJECT) call run(model%c_compiler//" -c " // target%source%file_name // target%compile_flags & - // " -o " // target%output_file) + // " -o " // target%output_file, echo=.true., exitstat=stat) case (FPM_TARGET_EXECUTABLE) -- cgit v1.2.3