Skip to content

Commit ab7cb42

Browse files
committed
Update: fpm_compiler & backend to redirect output to log files
1 parent b628302 commit ab7cb42

File tree

4 files changed

+61
-16
lines changed

4 files changed

+61
-16
lines changed

src/fpm_backend.F90

Lines changed: 37 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,7 @@ module fpm_backend
3030
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
3131
use fpm_error, only : fpm_stop
3232
use fpm_environment, only: run, get_os_type, OS_WINDOWS
33-
use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir
33+
use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir, LINE_BUFFER_LEN
3434
use fpm_model, only: fpm_model_t
3535
use fpm_strings, only: string_t, operator(.in.)
3636
use fpm_targets, only: build_target_t, build_target_ptr, FPM_TARGET_OBJECT, &
@@ -142,6 +142,11 @@ subroutine build_package(targets,model,verbose)
142142
! Check if this schedule region failed: exit with message if failed
143143
if (build_failed) then
144144
write(*,*) ''
145+
do j=1,size(stat)
146+
if (stat(j) /= 0) Then
147+
call print_build_log(queue(j)%ptr)
148+
end if
149+
end do
145150
do j=1,size(stat)
146151
if (stat(j) /= 0) then
147152
write(stderr,'(*(g0:,1x))') '<ERROR> Compilation failed for object "',basename(queue(j)%ptr%output_file),'"'
@@ -315,18 +320,19 @@ subroutine build_target(model,target,verbose,stat)
315320

316321
case (FPM_TARGET_OBJECT)
317322
call model%compiler%compile_fortran(target%source%file_name, target%output_file, &
318-
& target%compile_flags, stat)
323+
& target%compile_flags, target%output_log_file, stat)
319324

320325
case (FPM_TARGET_C_OBJECT)
321326
call model%compiler%compile_c(target%source%file_name, target%output_file, &
322-
& target%compile_flags, stat)
327+
& target%compile_flags, target%output_log_file, stat)
323328

324329
case (FPM_TARGET_EXECUTABLE)
325330
call model%compiler%link(target%output_file, &
326-
& target%compile_flags//" "//target%link_flags, stat)
331+
& target%compile_flags//" "//target%link_flags, target%output_log_file, stat)
327332

328333
case (FPM_TARGET_ARCHIVE)
329-
call model%archiver%make_archive(target%output_file, target%link_objects, stat)
334+
call model%archiver%make_archive(target%output_file, target%link_objects, &
335+
& target%output_log_file, stat)
330336

331337
end select
332338

@@ -339,4 +345,30 @@ subroutine build_target(model,target,verbose,stat)
339345
end subroutine build_target
340346

341347

348+
!> Read and print the build log for target
349+
!>
350+
subroutine print_build_log(target)
351+
type(build_target_t), intent(in), target :: target
352+
353+
integer :: fh, ios
354+
character(LINE_BUFFER_LEN) :: line
355+
356+
if (exists(target%output_log_file)) then
357+
358+
open(newunit=fh,file=target%output_log_file,status='old')
359+
do
360+
read(fh, '(A)', iostat=ios) line
361+
if (ios /= 0) exit
362+
write(*,'(A)') trim(line)
363+
end do
364+
close(fh)
365+
366+
else
367+
368+
write(stderr,'(*(g0:,1x))') '<ERROR> Unable to find build log "',basename(target%output_log_file),'"'
369+
370+
end if
371+
372+
end subroutine print_build_log
373+
342374
end module fpm_backend

src/fpm_compiler.f90

Lines changed: 17 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -686,7 +686,7 @@ end subroutine new_archiver
686686

687687

688688
!> Compile a Fortran object
689-
subroutine compile_fortran(self, input, output, args, stat)
689+
subroutine compile_fortran(self, input, output, args, log_file, stat)
690690
!> Instance of the compiler object
691691
class(compiler_t), intent(in) :: self
692692
!> Source file input
@@ -695,16 +695,18 @@ subroutine compile_fortran(self, input, output, args, stat)
695695
character(len=*), intent(in) :: output
696696
!> Arguments for compiler
697697
character(len=*), intent(in) :: args
698+
!> Compiler output log file
699+
character(len=*), intent(in) :: log_file
698700
!> Status flag
699701
integer, intent(out) :: stat
700702

701703
call run(self%fc // " -c " // input // " " // args // " -o " // output, &
702-
& echo=self%echo, verbose=self%verbose, exitstat=stat)
704+
& echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
703705
end subroutine compile_fortran
704706

705707

706708
!> Compile a C object
707-
subroutine compile_c(self, input, output, args, stat)
709+
subroutine compile_c(self, input, output, args, log_file, stat)
708710
!> Instance of the compiler object
709711
class(compiler_t), intent(in) :: self
710712
!> Source file input
@@ -713,49 +715,55 @@ subroutine compile_c(self, input, output, args, stat)
713715
character(len=*), intent(in) :: output
714716
!> Arguments for compiler
715717
character(len=*), intent(in) :: args
718+
!> Compiler output log file
719+
character(len=*), intent(in) :: log_file
716720
!> Status flag
717721
integer, intent(out) :: stat
718722

719723
call run(self%cc // " -c " // input // " " // args // " -o " // output, &
720-
& echo=self%echo, verbose=self%verbose, exitstat=stat)
724+
& echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
721725
end subroutine compile_c
722726

723727

724728
!> Link an executable
725-
subroutine link(self, output, args, stat)
729+
subroutine link(self, output, args, log_file, stat)
726730
!> Instance of the compiler object
727731
class(compiler_t), intent(in) :: self
728732
!> Output file of object
729733
character(len=*), intent(in) :: output
730734
!> Arguments for compiler
731735
character(len=*), intent(in) :: args
736+
!> Compiler output log file
737+
character(len=*), intent(in) :: log_file
732738
!> Status flag
733739
integer, intent(out) :: stat
734740

735741
call run(self%fc // " " // args // " -o " // output, echo=self%echo, &
736-
& verbose=self%verbose, exitstat=stat)
742+
& verbose=self%verbose, redirect=log_file, exitstat=stat)
737743
end subroutine link
738744

739745

740746
!> Create an archive
741-
subroutine make_archive(self, output, args, stat)
747+
subroutine make_archive(self, output, args, log_file, stat)
742748
!> Instance of the archiver object
743749
class(archiver_t), intent(in) :: self
744750
!> Name of the archive to generate
745751
character(len=*), intent(in) :: output
746752
!> Object files to include into the archive
747753
type(string_t), intent(in) :: args(:)
754+
!> Compiler output log file
755+
character(len=*), intent(in) :: log_file
748756
!> Status flag
749757
integer, intent(out) :: stat
750758

751759
if (self%use_response_file) then
752760
call write_response_file(output//".resp" , args)
753761
call run(self%ar // output // " @" // output//".resp", echo=self%echo, &
754-
& verbose=self%verbose, exitstat=stat)
762+
& verbose=self%verbose, redirect=log_file, exitstat=stat)
755763
call delete_file(output//".resp")
756764
else
757765
call run(self%ar // output // " " // string_cat(args, " "), &
758-
& echo=self%echo, verbose=self%verbose, exitstat=stat)
766+
& echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
759767
end if
760768
end subroutine make_archive
761769

src/fpm_filesystem.F90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ module fpm_filesystem
1515
mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file
1616
public :: fileopen, fileclose, filewrite, warnwrite, parent_dir
1717
public :: read_lines, read_lines_expanded
18-
public :: which
18+
public :: which, LINE_BUFFER_LEN
1919

2020
integer, parameter :: LINE_BUFFER_LEN = 1000
2121

src/fpm_targets.f90

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -75,6 +75,9 @@ module fpm_targets
7575
!> File path of output directory
7676
character(:), allocatable :: output_dir
7777

78+
!> File path of build log file relative to cwd
79+
character(:), allocatable :: output_log_file
80+
7881
!> Primary source for this build target
7982
type(srcfile_t), allocatable :: source
8083

@@ -491,6 +494,7 @@ subroutine resolve_target_linking(targets, model)
491494
end if
492495
target%output_dir = get_output_dir(model%build_prefix, target%compile_flags)
493496
target%output_file = join_path(target%output_dir, target%output_name)
497+
target%output_log_file = join_path(target%output_dir, target%output_name)//'.log'
494498
end associate
495499

496500
end do
@@ -528,7 +532,8 @@ subroutine resolve_target_linking(targets, model)
528532
target%output_dir = get_output_dir(model%build_prefix, &
529533
& target%compile_flags//local_link_flags)
530534
target%output_file = join_path(target%output_dir, target%output_name)
531-
end if
535+
target%output_log_file = join_path(target%output_dir, target%output_name)//'.log'
536+
end if
532537

533538
end associate
534539

0 commit comments

Comments
 (0)