diff options
-rw-r--r-- | src/fpm_backend.F90 | 42 | ||||
-rw-r--r-- | src/fpm_compiler.f90 | 26 | ||||
-rw-r--r-- | src/fpm_filesystem.F90 | 2 | ||||
-rw-r--r-- | src/fpm_targets.f90 | 7 |
4 files changed, 61 insertions, 16 deletions
diff --git a/src/fpm_backend.F90 b/src/fpm_backend.F90 index af50162..cb2dbc0 100644 --- a/src/fpm_backend.F90 +++ b/src/fpm_backend.F90 @@ -30,7 +30,7 @@ module fpm_backend use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit use fpm_error, only : fpm_stop use fpm_environment, only: run, get_os_type, OS_WINDOWS -use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir +use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir, LINE_BUFFER_LEN use fpm_model, only: fpm_model_t use fpm_strings, only: string_t, operator(.in.) use fpm_targets, only: build_target_t, build_target_ptr, FPM_TARGET_OBJECT, & @@ -143,6 +143,11 @@ subroutine build_package(targets,model,verbose) if (build_failed) then write(*,*) '' do j=1,size(stat) + if (stat(j) /= 0) Then + call print_build_log(queue(j)%ptr) + end if + end do + do j=1,size(stat) if (stat(j) /= 0) then write(stderr,'(*(g0:,1x))') '<ERROR> Compilation failed for object "',basename(queue(j)%ptr%output_file),'"' end if @@ -315,18 +320,19 @@ subroutine build_target(model,target,verbose,stat) case (FPM_TARGET_OBJECT) call model%compiler%compile_fortran(target%source%file_name, target%output_file, & - & target%compile_flags, stat) + & target%compile_flags, target%output_log_file, stat) case (FPM_TARGET_C_OBJECT) call model%compiler%compile_c(target%source%file_name, target%output_file, & - & target%compile_flags, stat) + & target%compile_flags, target%output_log_file, stat) case (FPM_TARGET_EXECUTABLE) call model%compiler%link(target%output_file, & - & target%compile_flags//" "//target%link_flags, stat) + & target%compile_flags//" "//target%link_flags, target%output_log_file, stat) case (FPM_TARGET_ARCHIVE) - call model%archiver%make_archive(target%output_file, target%link_objects, stat) + call model%archiver%make_archive(target%output_file, target%link_objects, & + & target%output_log_file, stat) end select @@ -339,4 +345,30 @@ subroutine build_target(model,target,verbose,stat) end subroutine build_target +!> Read and print the build log for target +!> +subroutine print_build_log(target) + type(build_target_t), intent(in), target :: target + + integer :: fh, ios + character(LINE_BUFFER_LEN) :: line + + if (exists(target%output_log_file)) then + + open(newunit=fh,file=target%output_log_file,status='old') + do + read(fh, '(A)', iostat=ios) line + if (ios /= 0) exit + write(*,'(A)') trim(line) + end do + close(fh) + + else + + write(stderr,'(*(g0:,1x))') '<ERROR> Unable to find build log "',basename(target%output_log_file),'"' + + end if + +end subroutine print_build_log + end module fpm_backend diff --git a/src/fpm_compiler.f90 b/src/fpm_compiler.f90 index e83d7a4..dba21b2 100644 --- a/src/fpm_compiler.f90 +++ b/src/fpm_compiler.f90 @@ -686,7 +686,7 @@ end subroutine new_archiver !> Compile a Fortran object -subroutine compile_fortran(self, input, output, args, stat) +subroutine compile_fortran(self, input, output, args, log_file, stat) !> Instance of the compiler object class(compiler_t), intent(in) :: self !> Source file input @@ -695,16 +695,18 @@ subroutine compile_fortran(self, input, output, args, stat) character(len=*), intent(in) :: output !> Arguments for compiler character(len=*), intent(in) :: args + !> Compiler output log file + character(len=*), intent(in) :: log_file !> Status flag integer, intent(out) :: stat call run(self%fc // " -c " // input // " " // args // " -o " // output, & - & echo=self%echo, verbose=self%verbose, exitstat=stat) + & echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat) end subroutine compile_fortran !> Compile a C object -subroutine compile_c(self, input, output, args, stat) +subroutine compile_c(self, input, output, args, log_file, stat) !> Instance of the compiler object class(compiler_t), intent(in) :: self !> Source file input @@ -713,49 +715,55 @@ subroutine compile_c(self, input, output, args, stat) character(len=*), intent(in) :: output !> Arguments for compiler character(len=*), intent(in) :: args + !> Compiler output log file + character(len=*), intent(in) :: log_file !> Status flag integer, intent(out) :: stat call run(self%cc // " -c " // input // " " // args // " -o " // output, & - & echo=self%echo, verbose=self%verbose, exitstat=stat) + & echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat) end subroutine compile_c !> Link an executable -subroutine link(self, output, args, stat) +subroutine link(self, output, args, log_file, stat) !> Instance of the compiler object class(compiler_t), intent(in) :: self !> Output file of object character(len=*), intent(in) :: output !> Arguments for compiler character(len=*), intent(in) :: args + !> Compiler output log file + character(len=*), intent(in) :: log_file !> Status flag integer, intent(out) :: stat call run(self%fc // " " // args // " -o " // output, echo=self%echo, & - & verbose=self%verbose, exitstat=stat) + & verbose=self%verbose, redirect=log_file, exitstat=stat) end subroutine link !> Create an archive -subroutine make_archive(self, output, args, stat) +subroutine make_archive(self, output, args, log_file, stat) !> Instance of the archiver object class(archiver_t), intent(in) :: self !> Name of the archive to generate character(len=*), intent(in) :: output !> Object files to include into the archive type(string_t), intent(in) :: args(:) + !> Compiler output log file + character(len=*), intent(in) :: log_file !> Status flag integer, intent(out) :: stat if (self%use_response_file) then call write_response_file(output//".resp" , args) call run(self%ar // output // " @" // output//".resp", echo=self%echo, & - & verbose=self%verbose, exitstat=stat) + & verbose=self%verbose, redirect=log_file, exitstat=stat) call delete_file(output//".resp") else call run(self%ar // output // " " // string_cat(args, " "), & - & echo=self%echo, verbose=self%verbose, exitstat=stat) + & echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat) end if end subroutine make_archive diff --git a/src/fpm_filesystem.F90 b/src/fpm_filesystem.F90 index 2b5b787..6127844 100644 --- a/src/fpm_filesystem.F90 +++ b/src/fpm_filesystem.F90 @@ -15,7 +15,7 @@ module fpm_filesystem mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file public :: fileopen, fileclose, filewrite, warnwrite, parent_dir public :: read_lines, read_lines_expanded - public :: which + public :: which, LINE_BUFFER_LEN integer, parameter :: LINE_BUFFER_LEN = 1000 diff --git a/src/fpm_targets.f90 b/src/fpm_targets.f90 index 7ea815b..122d73a 100644 --- a/src/fpm_targets.f90 +++ b/src/fpm_targets.f90 @@ -75,6 +75,9 @@ type build_target_t !> File path of output directory character(:), allocatable :: output_dir + !> File path of build log file relative to cwd + character(:), allocatable :: output_log_file + !> Primary source for this build target type(srcfile_t), allocatable :: source @@ -491,6 +494,7 @@ subroutine resolve_target_linking(targets, model) end if target%output_dir = get_output_dir(model%build_prefix, target%compile_flags) target%output_file = join_path(target%output_dir, target%output_name) + target%output_log_file = join_path(target%output_dir, target%output_name)//'.log' end associate end do @@ -528,7 +532,8 @@ subroutine resolve_target_linking(targets, model) target%output_dir = get_output_dir(model%build_prefix, & & target%compile_flags//local_link_flags) target%output_file = join_path(target%output_dir, target%output_name) - end if + target%output_log_file = join_path(target%output_dir, target%output_name)//'.log' + end if end associate |