Skip to content

Commit bffe22c

Browse files
committed
dump compile_commands.json at end of build
1 parent b4bc385 commit bffe22c

File tree

2 files changed

+24
-4
lines changed

2 files changed

+24
-4
lines changed

src/fpm_backend.F90

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@
2828
module fpm_backend
2929

3030
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
31-
use fpm_error, only : fpm_stop
31+
use fpm_error, only : fpm_stop, error_t
3232
use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir, run, getline
3333
use fpm_model, only: fpm_model_t
3434
use fpm_strings, only: string_t, operator(.in.)
@@ -65,6 +65,7 @@ subroutine build_package(targets,model,verbose)
6565
logical :: build_failed, skip_current
6666
type(string_t), allocatable :: build_dirs(:)
6767
type(string_t) :: temp
68+
type(error_t), allocatable :: error
6869

6970
type(build_progress_t) :: progress
7071
logical :: plain_output
@@ -157,6 +158,8 @@ subroutine build_package(targets,model,verbose)
157158
end do
158159

159160
call progress%success()
161+
call progress%dump_commands(error)
162+
if (allocated(error)) call fpm_stop(1,'error writing compile_commands.json: '//trim(error%message))
160163

161164
end subroutine build_package
162165

src/fpm_backend_output.f90

Lines changed: 20 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,8 @@
1111

1212
module fpm_backend_output
1313
use iso_fortran_env, only: stdout=>output_unit
14-
use fpm_filesystem, only: basename
14+
use fpm_error, only: error_t
15+
use fpm_filesystem, only: basename,join_path
1516
use fpm_targets, only: build_target_ptr
1617
use fpm_backend_console, only: console_t, LINE_RESET, COLOR_RED, COLOR_GREEN, COLOR_YELLOW, COLOR_RESET
1718
use fpm_compile_commands, only: compile_command_t, compile_command_table_t
@@ -43,6 +44,8 @@ module fpm_backend_output
4344
procedure :: completed_status => output_status_complete
4445
!> Output finished status for whole package
4546
procedure :: success => output_progress_success
47+
!> Output 'compile_commands.json' to build/ folder
48+
procedure :: dump_commands => output_write_compile_commands
4649
end type build_progress_t
4750

4851
!> Constructor for build_progress_t
@@ -167,7 +170,7 @@ end subroutine output_status_complete
167170
!> Output finished status for whole package
168171
subroutine output_progress_success(progress)
169172
class(build_progress_t), intent(inout) :: progress
170-
173+
171174
if (progress%plain_mode) then ! Plain output
172175

173176
write(*,'(A)') '[100%] Project compiled successfully.'
@@ -177,7 +180,21 @@ subroutine output_progress_success(progress)
177180
write(*,'(A)') LINE_RESET//COLOR_GREEN//'[100%] Project compiled successfully.'//COLOR_RESET
178181

179182
end if
180-
183+
181184
end subroutine output_progress_success
185+
186+
!> Write compile commands table
187+
subroutine output_write_compile_commands(progress,error)
188+
class(build_progress_t), intent(inout) :: progress
189+
190+
character(:), allocatable :: path
191+
type(error_t), allocatable :: error
192+
193+
! Write compile commands
194+
path = join_path('build','compile_commands.json')
195+
196+
call progress%compile_commands%dump(file=path, error=error, json=.true.)
197+
198+
end subroutine output_write_compile_commands
182199

183200
end module fpm_backend_output

0 commit comments

Comments
 (0)