Skip to content

Commit bdf9568

Browse files
committed
create compile_commands.json on dry run fpm build --list
1 parent 1379f8e commit bdf9568

File tree

4 files changed

+80
-28
lines changed

4 files changed

+80
-28
lines changed

src/fpm.f90

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -461,10 +461,11 @@ subroutine cmd_build(settings)
461461
do i=1,size(targets)
462462
write(stderr,*) targets(i)%ptr%output_file
463463
enddo
464-
else if (settings%show_model) then
464+
endif
465+
if (settings%show_model) then
465466
call show_model(model)
466467
else
467-
call build_package(targets,model,verbose=settings%verbose)
468+
call build_package(targets,model,verbose=settings%verbose,dry_run=settings%list)
468469
endif
469470

470471
end subroutine cmd_build
@@ -573,7 +574,7 @@ subroutine cmd_run(settings,test)
573574

574575
end if
575576

576-
call build_package(targets,model,verbose=settings%verbose)
577+
call build_package(targets,model,verbose=settings%verbose,dry_run=settings%list)
577578

578579
if (settings%list) then
579580
call compact_list()

src/fpm/cmd/install.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,7 @@ subroutine cmd_install(settings)
5353
end if
5454

5555
if (.not.settings%no_rebuild) then
56-
call build_package(targets,model,verbose=settings%verbose)
56+
call build_package(targets,model,verbose=settings%verbose,dry_run=settings%list)
5757
end if
5858

5959
call new_installer(installer, prefix=settings%prefix, &

src/fpm_backend.F90

Lines changed: 19 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -54,11 +54,15 @@ function c_isatty() bind(C, name = 'c_isatty')
5454
contains
5555

5656
!> Top-level routine to build package described by `model`
57-
subroutine build_package(targets,model,verbose)
57+
subroutine build_package(targets,model,verbose,dry_run)
5858
type(build_target_ptr), intent(inout) :: targets(:)
5959
type(fpm_model_t), intent(in) :: model
6060
logical, intent(in) :: verbose
61-
61+
62+
!> If dry_run, the build process is only mocked, but the list of compile_commands
63+
!> is still created
64+
logical, intent(in) :: dry_run
65+
6266
integer :: i, j
6367
type(build_target_ptr), allocatable :: queue(:)
6468
integer, allocatable :: schedule_ptr(:), stat(:)
@@ -81,7 +85,7 @@ subroutine build_package(targets,model,verbose)
8185
end do
8286

8387
do i = 1, size(build_dirs)
84-
call mkdir(build_dirs(i)%s,verbose)
88+
if (.not.dry_run) call mkdir(build_dirs(i)%s,verbose)
8589
end do
8690

8791
! Perform depth-first topological sort of targets
@@ -95,14 +99,13 @@ subroutine build_package(targets,model,verbose)
9599
call schedule_targets(queue, schedule_ptr, targets)
96100

97101
! Check if queue is empty
98-
if (.not.verbose .and. size(queue) < 1) then
102+
if (.not.verbose .and. size(queue) < 1 .and. .not.dry_run) then
99103
write(stderr, '(a)') 'Project is up to date'
100104
return
101105
end if
102106

103107
! Initialise build status flags
104-
allocate(stat(size(queue)))
105-
stat(:) = 0
108+
allocate(stat(size(queue)),source=0)
106109
build_failed = .false.
107110

108111
! Set output mode
@@ -126,9 +129,10 @@ subroutine build_package(targets,model,verbose)
126129
skip_current = build_failed
127130

128131
if (.not.skip_current) then
129-
call progress%compiling_status(j)
130-
call build_target(model,queue(j)%ptr,verbose,progress%compile_commands,stat(j))
131-
call progress%completed_status(j,stat(j))
132+
if (.not.dry_run) call progress%compiling_status(j)
133+
call build_target(model,queue(j)%ptr,verbose,dry_run, &
134+
progress%compile_commands,stat(j))
135+
if (.not.dry_run) call progress%completed_status(j,stat(j))
132136
end if
133137

134138
! Set global flag if this target failed to build
@@ -157,7 +161,7 @@ subroutine build_package(targets,model,verbose)
157161

158162
end do
159163

160-
call progress%success()
164+
if (.not.dry_run) call progress%success()
161165
call progress%dump_commands(error)
162166
if (allocated(error)) call fpm_stop(1,'error writing compile_commands.json: '//trim(error%message))
163167

@@ -304,17 +308,19 @@ end subroutine schedule_targets
304308
!>
305309
!> If successful, also caches the source file digest to disk.
306310
!>
307-
subroutine build_target(model,target,verbose,table,stat)
311+
subroutine build_target(model,target,verbose,dry_run,table,stat)
308312
type(fpm_model_t), intent(in) :: model
309313
type(build_target_t), intent(in), target :: target
310314
logical, intent(in) :: verbose
315+
!> If dry_run, the build process is only mocked, but compile_commands are still created
316+
logical, intent(in) :: dry_run
311317
type(compile_command_table_t), intent(inout) :: table
312318
integer, intent(out) :: stat
313319

314320
integer :: fh
315321

316322
!$omp critical
317-
if (.not.exists(dirname(target%output_file))) then
323+
if (.not.exists(dirname(target%output_file)) .and. .not.dry_run) then
318324
call mkdir(dirname(target%output_file),verbose)
319325
end if
320326
!$omp end critical
@@ -343,7 +349,7 @@ subroutine build_target(model,target,verbose,table,stat)
343349

344350
end select
345351

346-
if (stat == 0 .and. allocated(target%source)) then
352+
if (stat == 0 .and. allocated(target%source) .and. .not.dry_run) then
347353
open(newunit=fh,file=target%output_file//'.digest',status='unknown')
348354
write(fh,*) target%source%digest
349355
close(fh)

src/fpm_compiler.F90

Lines changed: 56 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1104,7 +1104,7 @@ end subroutine new_archiver
11041104

11051105

11061106
!> Compile a Fortran object
1107-
subroutine compile_fortran(self, input, output, args, log_file, stat, table)
1107+
subroutine compile_fortran(self, input, output, args, log_file, stat, table, dry_run)
11081108
!> Instance of the compiler object
11091109
class(compiler_t), intent(in) :: self
11101110
!> Source file input
@@ -1119,16 +1119,25 @@ subroutine compile_fortran(self, input, output, args, log_file, stat, table)
11191119
integer, intent(out) :: stat
11201120
!> Optional compile_commands table
11211121
type(compile_command_table_t), optional, intent(inout) :: table
1122+
!> Optional mocking
1123+
logical, optional, intent(in) :: dry_run
11221124

11231125
character(len=:), allocatable :: command
11241126
type(error_t), allocatable :: error
1127+
logical :: mock
1128+
1129+
! Check if we're actually building this file
1130+
mock = .false.
1131+
if (present(dry_run)) mock = dry_run
11251132

11261133
! Set command
11271134
command = self%fc // " -c " // input // " " // args // " -o " // output
11281135

11291136
! Execute command
1130-
call run(command, echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
1131-
if (stat/=0) return
1137+
if (.not.mock) then
1138+
call run(command, echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
1139+
if (stat/=0) return
1140+
endif
11321141

11331142
! Optionally register compile command
11341143
if (present(table)) then
@@ -1140,7 +1149,7 @@ end subroutine compile_fortran
11401149

11411150

11421151
!> Compile a C object
1143-
subroutine compile_c(self, input, output, args, log_file, stat, table)
1152+
subroutine compile_c(self, input, output, args, log_file, stat, table, dry_run)
11441153
!> Instance of the compiler object
11451154
class(compiler_t), intent(in) :: self
11461155
!> Source file input
@@ -1155,16 +1164,25 @@ subroutine compile_c(self, input, output, args, log_file, stat, table)
11551164
integer, intent(out) :: stat
11561165
!> Optional compile_commands table
11571166
type(compile_command_table_t), optional, intent(inout) :: table
1167+
!> Optional mocking
1168+
logical, optional, intent(in) :: dry_run
11581169

11591170
character(len=:), allocatable :: command
11601171
type(error_t), allocatable :: error
1172+
logical :: mock
1173+
1174+
! Check if we're actually building this file
1175+
mock = .false.
1176+
if (present(dry_run)) mock = dry_run
11611177

11621178
! Set command
11631179
command = self%cc // " -c " // input // " " // args // " -o " // output
11641180

11651181
! Execute command
1166-
call run(command, echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
1167-
if (stat/=0) return
1182+
if (.not.mock) then
1183+
call run(command, echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
1184+
if (stat/=0) return
1185+
endif
11681186

11691187
! Optionally register compile command
11701188
if (present(table)) then
@@ -1175,7 +1193,7 @@ subroutine compile_c(self, input, output, args, log_file, stat, table)
11751193
end subroutine compile_c
11761194

11771195
!> Compile a CPP object
1178-
subroutine compile_cpp(self, input, output, args, log_file, stat, table)
1196+
subroutine compile_cpp(self, input, output, args, log_file, stat, table, dry_run)
11791197
!> Instance of the compiler object
11801198
class(compiler_t), intent(in) :: self
11811199
!> Source file input
@@ -1190,16 +1208,25 @@ subroutine compile_cpp(self, input, output, args, log_file, stat, table)
11901208
integer, intent(out) :: stat
11911209
!> Optional compile_commands table
11921210
type(compile_command_table_t), optional, intent(inout) :: table
1211+
!> Optional mocking
1212+
logical, optional, intent(in) :: dry_run
11931213

11941214
character(len=:), allocatable :: command
11951215
type(error_t), allocatable :: error
1216+
logical :: mock
1217+
1218+
! Check if we're actually building this file
1219+
mock = .false.
1220+
if (present(dry_run)) mock = dry_run
11961221

11971222
! Set command
11981223
command = self%cxx // " -c " // input // " " // args // " -o " // output
11991224

12001225
! Execute command
1201-
call run(command, echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
1202-
if (stat/=0) return
1226+
if (.not.mock) then
1227+
call run(command, echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
1228+
if (stat/=0) return
1229+
endif
12031230

12041231
! Optionally register compile command
12051232
if (present(table)) then
@@ -1210,7 +1237,7 @@ subroutine compile_cpp(self, input, output, args, log_file, stat, table)
12101237
end subroutine compile_cpp
12111238

12121239
!> Link an executable
1213-
subroutine link_executable(self, output, args, log_file, stat)
1240+
subroutine link_executable(self, output, args, log_file, stat, dry_run)
12141241
!> Instance of the compiler object
12151242
class(compiler_t), intent(in) :: self
12161243
!> Output file of object
@@ -1221,13 +1248,21 @@ subroutine link_executable(self, output, args, log_file, stat)
12211248
character(len=*), intent(in) :: log_file
12221249
!> Status flag
12231250
integer, intent(out) :: stat
1251+
!> Optional mocking
1252+
logical, optional, intent(in) :: dry_run
12241253

12251254
character(len=:), allocatable :: command
1255+
logical :: mock
1256+
1257+
! Check if we're actually linking
1258+
mock = .false.
1259+
if (present(dry_run)) mock = dry_run
12261260

12271261
! Set command
12281262
command = self%fc // " " // args // " -o " // output
12291263

12301264
! Execute command
1265+
if (.not.mock) &
12311266
call run(command, echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
12321267

12331268
end subroutine link_executable
@@ -1236,7 +1271,7 @@ end subroutine link_executable
12361271
!> @todo For Windows OS, use the local `delete_file_win32` in stead of `delete_file`.
12371272
!> This may be related to a bug in Mingw64-openmp and is expected to be resolved in the future,
12381273
!> see issue #707, #708 and #808.
1239-
subroutine make_archive(self, output, args, log_file, stat)
1274+
subroutine make_archive(self, output, args, log_file, stat, dry_run)
12401275
!> Instance of the archiver object
12411276
class(archiver_t), intent(in) :: self
12421277
!> Name of the archive to generate
@@ -1247,6 +1282,16 @@ subroutine make_archive(self, output, args, log_file, stat)
12471282
character(len=*), intent(in) :: log_file
12481283
!> Status flag
12491284
integer, intent(out) :: stat
1285+
!> Optional mocking
1286+
logical, optional, intent(in) :: dry_run
1287+
1288+
logical :: mock
1289+
1290+
! Check if we're actually linking
1291+
mock = .false.
1292+
if (present(dry_run)) mock = dry_run
1293+
1294+
if (mock) return
12501295

12511296
if (self%use_response_file) then
12521297
call write_response_file(output//".resp" , args)

0 commit comments

Comments
 (0)