@@ -43,7 +43,7 @@ module fpm_compiler
43
43
use fpm_manifest, only : package_config_t
44
44
use fpm_error, only: error_t, fatal_error
45
45
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
47
47
implicit none
48
48
public :: compiler_t, new_compiler, archiver_t, new_archiver, get_macros
49
49
public :: debug
@@ -1097,7 +1097,7 @@ end subroutine new_archiver
1097
1097
1098
1098
1099
1099
! > 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 )
1101
1101
! > Instance of the compiler object
1102
1102
class(compiler_t), intent (in ) :: self
1103
1103
! > Source file input
@@ -1110,14 +1110,30 @@ subroutine compile_fortran(self, input, output, args, log_file, stat)
1110
1110
character (len=* ), intent (in ) :: log_file
1111
1111
! > Status flag
1112
1112
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
1113
1121
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
+
1116
1132
end subroutine compile_fortran
1117
1133
1118
1134
1119
1135
! > 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 )
1121
1137
! > Instance of the compiler object
1122
1138
class(compiler_t), intent (in ) :: self
1123
1139
! > Source file input
@@ -1130,13 +1146,29 @@ subroutine compile_c(self, input, output, args, log_file, stat)
1130
1146
character (len=* ), intent (in ) :: log_file
1131
1147
! > Status flag
1132
1148
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
1133
1157
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
+
1136
1168
end subroutine compile_c
1137
1169
1138
1170
! > 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 )
1140
1172
! > Instance of the compiler object
1141
1173
class(compiler_t), intent (in ) :: self
1142
1174
! > Source file input
@@ -1149,9 +1181,25 @@ subroutine compile_cpp(self, input, output, args, log_file, stat)
1149
1181
character (len=* ), intent (in ) :: log_file
1150
1182
! > Status flag
1151
1183
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
1152
1192
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
+
1155
1203
end subroutine compile_cpp
1156
1204
1157
1205
! > Link an executable
@@ -1166,12 +1214,17 @@ subroutine link(self, output, args, log_file, stat)
1166
1214
character (len=* ), intent (in ) :: log_file
1167
1215
! > Status flag
1168
1216
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
+
1172
1226
end subroutine link
1173
1227
1174
-
1175
1228
! > Create an archive
1176
1229
! > @todo For Windows OS, use the local `delete_file_win32` in stead of `delete_file`.
1177
1230
! > This may be related to a bug in Mingw64-openmp and is expected to be resolved in the future,
0 commit comments