Skip to content

Commit 9a1d3ad

Browse files
committed
register compile commands into the compiler
1 parent 58811b2 commit 9a1d3ad

File tree

1 file changed

+67
-14
lines changed

1 file changed

+67
-14
lines changed

src/fpm_compiler.F90

Lines changed: 67 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@ module fpm_compiler
4343
use fpm_manifest, only : package_config_t
4444
use fpm_error, only: error_t, fatal_error
4545
use fpm_toml, only: serializable_t, toml_table, set_string, set_value, toml_stat, get_value
46-
use fpm_compile_commands, only: compile_command_t
46+
use fpm_compile_commands, only: compile_command_t, compile_command_table_t
4747
implicit none
4848
public :: compiler_t, new_compiler, archiver_t, new_archiver, get_macros
4949
public :: debug
@@ -1097,7 +1097,7 @@ end subroutine new_archiver
10971097

10981098

10991099
!> Compile a Fortran object
1100-
subroutine compile_fortran(self, input, output, args, log_file, stat)
1100+
subroutine compile_fortran(self, input, output, args, log_file, stat, table)
11011101
!> Instance of the compiler object
11021102
class(compiler_t), intent(in) :: self
11031103
!> Source file input
@@ -1110,14 +1110,30 @@ subroutine compile_fortran(self, input, output, args, log_file, stat)
11101110
character(len=*), intent(in) :: log_file
11111111
!> Status flag
11121112
integer, intent(out) :: stat
1113+
!> Optional compile_commands table
1114+
type(compile_command_table_t), optional, intent(inout) :: table
1115+
1116+
character(len=:), allocatable :: command
1117+
type(error_t), allocatable :: error
1118+
1119+
! Set command
1120+
command = self%fc // " -c " // input // " " // args // " -o " // output
11131121

1114-
call run(self%fc // " -c " // input // " " // args // " -o " // output, &
1115-
& echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
1122+
! Execute command
1123+
call run(command, echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
1124+
if (stat/=0) return
1125+
1126+
! Optionally register compile command
1127+
if (present(table)) then
1128+
call table%register(command, error)
1129+
stat = merge(-1,0,allocated(error))
1130+
endif
1131+
11161132
end subroutine compile_fortran
11171133

11181134

11191135
!> Compile a C object
1120-
subroutine compile_c(self, input, output, args, log_file, stat)
1136+
subroutine compile_c(self, input, output, args, log_file, stat, table)
11211137
!> Instance of the compiler object
11221138
class(compiler_t), intent(in) :: self
11231139
!> Source file input
@@ -1130,13 +1146,29 @@ subroutine compile_c(self, input, output, args, log_file, stat)
11301146
character(len=*), intent(in) :: log_file
11311147
!> Status flag
11321148
integer, intent(out) :: stat
1149+
!> Optional compile_commands table
1150+
type(compile_command_table_t), optional, intent(inout) :: table
1151+
1152+
character(len=:), allocatable :: command
1153+
type(error_t), allocatable :: error
1154+
1155+
! Set command
1156+
command = self%cc // " -c " // input // " " // args // " -o " // output
11331157

1134-
call run(self%cc // " -c " // input // " " // args // " -o " // output, &
1135-
& echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
1158+
! Execute command
1159+
call run(command, echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
1160+
if (stat/=0) return
1161+
1162+
! Optionally register compile command
1163+
if (present(table)) then
1164+
call table%register(command, error)
1165+
stat = merge(-1,0,allocated(error))
1166+
endif
1167+
11361168
end subroutine compile_c
11371169

11381170
!> Compile a CPP object
1139-
subroutine compile_cpp(self, input, output, args, log_file, stat)
1171+
subroutine compile_cpp(self, input, output, args, log_file, stat, table)
11401172
!> Instance of the compiler object
11411173
class(compiler_t), intent(in) :: self
11421174
!> Source file input
@@ -1149,9 +1181,25 @@ subroutine compile_cpp(self, input, output, args, log_file, stat)
11491181
character(len=*), intent(in) :: log_file
11501182
!> Status flag
11511183
integer, intent(out) :: stat
1184+
!> Optional compile_commands table
1185+
type(compile_command_table_t), optional, intent(inout) :: table
1186+
1187+
character(len=:), allocatable :: command
1188+
type(error_t), allocatable :: error
1189+
1190+
! Set command
1191+
command = self%cxx // " -c " // input // " " // args // " -o " // output
11521192

1153-
call run(self%cxx // " -c " // input // " " // args // " -o " // output, &
1154-
& echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
1193+
! Execute command
1194+
call run(command, echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
1195+
if (stat/=0) return
1196+
1197+
! Optionally register compile command
1198+
if (present(table)) then
1199+
call table%register(command, error)
1200+
stat = merge(-1,0,allocated(error))
1201+
endif
1202+
11551203
end subroutine compile_cpp
11561204

11571205
!> Link an executable
@@ -1166,12 +1214,17 @@ subroutine link(self, output, args, log_file, stat)
11661214
character(len=*), intent(in) :: log_file
11671215
!> Status flag
11681216
integer, intent(out) :: stat
1169-
1170-
call run(self%fc // " " // args // " -o " // output, echo=self%echo, &
1171-
& verbose=self%verbose, redirect=log_file, exitstat=stat)
1217+
1218+
character(len=:), allocatable :: command
1219+
1220+
! Set command
1221+
command = self%fc // " " // args // " -o " // output
1222+
1223+
! Execute command
1224+
call run(command, echo=self%echo, verbose=self%verbose, redirect=log_file, exitstat=stat)
1225+
11721226
end subroutine link
11731227

1174-
11751228
!> Create an archive
11761229
!> @todo For Windows OS, use the local `delete_file_win32` in stead of `delete_file`.
11771230
!> This may be related to a bug in Mingw64-openmp and is expected to be resolved in the future,

0 commit comments

Comments
 (0)