@@ -1104,7 +1104,7 @@ end subroutine new_archiver
1104
1104
1105
1105
1106
1106
! > 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 )
1108
1108
! > Instance of the compiler object
1109
1109
class(compiler_t), intent (in ) :: self
1110
1110
! > Source file input
@@ -1119,16 +1119,25 @@ subroutine compile_fortran(self, input, output, args, log_file, stat, table)
1119
1119
integer , intent (out ) :: stat
1120
1120
! > Optional compile_commands table
1121
1121
type (compile_command_table_t), optional , intent (inout ) :: table
1122
+ ! > Optional mocking
1123
+ logical , optional , intent (in ) :: dry_run
1122
1124
1123
1125
character (len= :), allocatable :: command
1124
1126
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
1125
1132
1126
1133
! Set command
1127
1134
command = self% fc // " -c " // input // " " // args // " -o " // output
1128
1135
1129
1136
! 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
1132
1141
1133
1142
! Optionally register compile command
1134
1143
if (present (table)) then
@@ -1140,7 +1149,7 @@ end subroutine compile_fortran
1140
1149
1141
1150
1142
1151
! > 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 )
1144
1153
! > Instance of the compiler object
1145
1154
class(compiler_t), intent (in ) :: self
1146
1155
! > Source file input
@@ -1155,16 +1164,25 @@ subroutine compile_c(self, input, output, args, log_file, stat, table)
1155
1164
integer , intent (out ) :: stat
1156
1165
! > Optional compile_commands table
1157
1166
type (compile_command_table_t), optional , intent (inout ) :: table
1167
+ ! > Optional mocking
1168
+ logical , optional , intent (in ) :: dry_run
1158
1169
1159
1170
character (len= :), allocatable :: command
1160
1171
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
1161
1177
1162
1178
! Set command
1163
1179
command = self% cc // " -c " // input // " " // args // " -o " // output
1164
1180
1165
1181
! 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
1168
1186
1169
1187
! Optionally register compile command
1170
1188
if (present (table)) then
@@ -1175,7 +1193,7 @@ subroutine compile_c(self, input, output, args, log_file, stat, table)
1175
1193
end subroutine compile_c
1176
1194
1177
1195
! > 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 )
1179
1197
! > Instance of the compiler object
1180
1198
class(compiler_t), intent (in ) :: self
1181
1199
! > Source file input
@@ -1190,16 +1208,25 @@ subroutine compile_cpp(self, input, output, args, log_file, stat, table)
1190
1208
integer , intent (out ) :: stat
1191
1209
! > Optional compile_commands table
1192
1210
type (compile_command_table_t), optional , intent (inout ) :: table
1211
+ ! > Optional mocking
1212
+ logical , optional , intent (in ) :: dry_run
1193
1213
1194
1214
character (len= :), allocatable :: command
1195
1215
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
1196
1221
1197
1222
! Set command
1198
1223
command = self% cxx // " -c " // input // " " // args // " -o " // output
1199
1224
1200
1225
! 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
1203
1230
1204
1231
! Optionally register compile command
1205
1232
if (present (table)) then
@@ -1210,7 +1237,7 @@ subroutine compile_cpp(self, input, output, args, log_file, stat, table)
1210
1237
end subroutine compile_cpp
1211
1238
1212
1239
! > 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 )
1214
1241
! > Instance of the compiler object
1215
1242
class(compiler_t), intent (in ) :: self
1216
1243
! > Output file of object
@@ -1221,13 +1248,21 @@ subroutine link_executable(self, output, args, log_file, stat)
1221
1248
character (len=* ), intent (in ) :: log_file
1222
1249
! > Status flag
1223
1250
integer , intent (out ) :: stat
1251
+ ! > Optional mocking
1252
+ logical , optional , intent (in ) :: dry_run
1224
1253
1225
1254
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
1226
1260
1227
1261
! Set command
1228
1262
command = self% fc // " " // args // " -o " // output
1229
1263
1230
1264
! Execute command
1265
+ if (.not. mock) &
1231
1266
call run(command, echo= self% echo, verbose= self% verbose, redirect= log_file, exitstat= stat)
1232
1267
1233
1268
end subroutine link_executable
@@ -1236,7 +1271,7 @@ end subroutine link_executable
1236
1271
! > @todo For Windows OS, use the local `delete_file_win32` in stead of `delete_file`.
1237
1272
! > This may be related to a bug in Mingw64-openmp and is expected to be resolved in the future,
1238
1273
! > 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 )
1240
1275
! > Instance of the archiver object
1241
1276
class(archiver_t), intent (in ) :: self
1242
1277
! > Name of the archive to generate
@@ -1247,6 +1282,16 @@ subroutine make_archive(self, output, args, log_file, stat)
1247
1282
character (len=* ), intent (in ) :: log_file
1248
1283
! > Status flag
1249
1284
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
1250
1295
1251
1296
if (self% use_response_file) then
1252
1297
call write_response_file(output// " .resp" , args)
0 commit comments