@@ -29,23 +29,33 @@ module fpm_backend
2929
3030use ,intrinsic :: iso_fortran_env, only : stdin= >input_unit, stdout= >output_unit, stderr= >error_unit
3131use fpm_error, only : fpm_stop
32- use fpm_environment, only: run, get_os_type, OS_WINDOWS
33- use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir
32+ use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir, run, getline
3433use fpm_model, only: fpm_model_t
3534use fpm_strings, only: string_t, operator (.in .)
3635use fpm_targets, only: build_target_t, build_target_ptr, FPM_TARGET_OBJECT, &
3736 FPM_TARGET_C_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
37+ use fpm_backend_output
3838implicit none
3939
4040private
4141public :: build_package, sort_target, schedule_targets
4242
43+ #ifndef FPM_BOOTSTRAP
44+ interface
45+ function c_isatty () bind(C, name = ' c_isatty' )
46+ use , intrinsic :: iso_c_binding, only: c_int
47+ integer (c_int) :: c_isatty
48+ end function
49+ end interface
50+ #endif
51+
4352contains
4453
4554! > Top-level routine to build package described by `model`
46- subroutine build_package (targets ,model )
55+ subroutine build_package (targets ,model , verbose )
4756 type (build_target_ptr), intent (inout ) :: targets(:)
4857 type (fpm_model_t), intent (in ) :: model
58+ logical , intent (in ) :: verbose
4959
5060 integer :: i, j
5161 type (build_target_ptr), allocatable :: queue(:)
@@ -54,6 +64,9 @@ subroutine build_package(targets,model)
5464 type (string_t), allocatable :: build_dirs(:)
5565 type (string_t) :: temp
5666
67+ type (build_progress_t) :: progress
68+ logical :: plain_output
69+
5770 ! Need to make output directory for include (mod) files
5871 allocate (build_dirs(0 ))
5972 do i = 1 , size (targets)
@@ -65,7 +78,7 @@ subroutine build_package(targets,model)
6578 end do
6679
6780 do i = 1 , size (build_dirs)
68- call mkdir(build_dirs(i)% s)
81+ call mkdir(build_dirs(i)% s,verbose )
6982 end do
7083
7184 ! Perform depth-first topological sort of targets
@@ -78,11 +91,26 @@ subroutine build_package(targets,model)
7891 ! Construct build schedule queue
7992 call schedule_targets(queue, schedule_ptr, targets)
8093
94+ ! Check if queue is empty
95+ if (.not. verbose .and. size (queue) < 1 ) then
96+ write (* , ' (a)' ) ' Project is up to date'
97+ return
98+ end if
99+
81100 ! Initialise build status flags
82101 allocate (stat(size (queue)))
83102 stat(:) = 0
84103 build_failed = .false.
85104
105+ ! Set output mode
106+ #ifndef FPM_BOOTSTRAP
107+ plain_output = (.not. (c_isatty()==1 )) .or. verbose
108+ #else
109+ plain_output = .true.
110+ #endif
111+
112+ progress = build_progress_t(queue,plain_output)
113+
86114 ! Loop over parallel schedule regions
87115 do i= 1 ,size (schedule_ptr)- 1
88116
@@ -95,7 +123,9 @@ subroutine build_package(targets,model)
95123 skip_current = build_failed
96124
97125 if (.not. skip_current) then
98- call build_target(model,queue(j)% ptr,stat(j))
126+ call progress% compiling_status(j)
127+ call build_target(model,queue(j)% ptr,verbose,stat(j))
128+ call progress% completed_status(j,stat(j))
99129 end if
100130
101131 ! Set global flag if this target failed to build
@@ -108,6 +138,12 @@ subroutine build_package(targets,model)
108138
109139 ! Check if this schedule region failed: exit with message if failed
110140 if (build_failed) then
141+ write (* ,* )
142+ do j= 1 ,size (stat)
143+ if (stat(j) /= 0 ) Then
144+ call print_build_log(queue(j)% ptr)
145+ end if
146+ end do
111147 do j= 1 ,size (stat)
112148 if (stat(j) /= 0 ) then
113149 write (stderr,' (*(g0:,1x))' ) ' <ERROR> Compilation failed for object "' ,basename(queue(j)% ptr% output_file),' "'
@@ -118,6 +154,8 @@ subroutine build_package(targets,model)
118154
119155 end do
120156
157+ call progress% success()
158+
121159end subroutine build_package
122160
123161
@@ -261,35 +299,37 @@ end subroutine schedule_targets
261299! >
262300! > If successful, also caches the source file digest to disk.
263301! >
264- subroutine build_target (model ,target ,stat )
302+ subroutine build_target (model ,target ,verbose , stat )
265303 type (fpm_model_t), intent (in ) :: model
266304 type (build_target_t), intent (in ), target :: target
305+ logical , intent (in ) :: verbose
267306 integer , intent (out ) :: stat
268307
269308 integer :: fh
270309
271310 ! $omp critical
272311 if (.not. exists(dirname(target % output_file))) then
273- call mkdir(dirname(target % output_file))
312+ call mkdir(dirname(target % output_file),verbose )
274313 end if
275314 ! $omp end critical
276315
277316 select case (target % target_type)
278317
279318 case (FPM_TARGET_OBJECT)
280319 call model% compiler% compile_fortran(target % source% file_name, target % output_file, &
281- & target % compile_flags, stat)
320+ & target % compile_flags, target % output_log_file, stat)
282321
283322 case (FPM_TARGET_C_OBJECT)
284323 call model% compiler% compile_c(target % source% file_name, target % output_file, &
285- & target % compile_flags, stat)
324+ & target % compile_flags, target % output_log_file, stat)
286325
287326 case (FPM_TARGET_EXECUTABLE)
288327 call model% compiler% link(target % output_file, &
289- & target % compile_flags// " " // target % link_flags, stat)
328+ & target % compile_flags// " " // target % link_flags, target % output_log_file, stat)
290329
291330 case (FPM_TARGET_ARCHIVE)
292- call model% archiver% make_archive(target % output_file, target % link_objects, stat)
331+ call model% archiver% make_archive(target % output_file, target % link_objects, &
332+ & target % output_log_file, stat)
293333
294334 end select
295335
@@ -302,4 +342,30 @@ subroutine build_target(model,target,stat)
302342end subroutine build_target
303343
304344
345+ ! > Read and print the build log for target
346+ ! >
347+ subroutine print_build_log (target )
348+ type (build_target_t), intent (in ), target :: target
349+
350+ integer :: fh, ios
351+ character (:), allocatable :: line
352+
353+ if (exists(target % output_log_file)) then
354+
355+ open (newunit= fh,file= target % output_log_file,status= ' old' )
356+ do
357+ call getline(fh, line, ios)
358+ if (ios /= 0 ) exit
359+ write (* ,' (A)' ) trim (line)
360+ end do
361+ close (fh)
362+
363+ else
364+
365+ write (stderr,' (*(g0:,1x))' ) ' <ERROR> Unable to find build log "' ,basename(target % output_log_file),' "'
366+
367+ end if
368+
369+ end subroutine print_build_log
370+
305371end module fpm_backend
0 commit comments