@@ -55,8 +55,34 @@ module fpm_compile_commands
55
55
56
56
end type compile_command_table_t
57
57
58
+ interface compile_command_t
59
+ module procedure cct_new
60
+ end interface compile_command_t
61
+
58
62
contains
59
63
64
+ ! > Override default initializer (GCC 15 bug)
65
+ type (compile_command_t) function cct_new(directory,arguments,file) result(cct)
66
+ character (len=* ), intent (in ) :: directory,file
67
+ character (len=* ), optional , intent (in ) :: arguments(:)
68
+
69
+ integer :: i,n
70
+
71
+ cct% directory = string_t(trim (directory))
72
+ cct% file = string_t(trim (file))
73
+
74
+ if (present (arguments)) then
75
+ n = size (arguments)
76
+ else
77
+ n = 0
78
+ endif
79
+ allocate (cct% arguments(n))
80
+ do i= 1 ,n
81
+ cct% arguments(i) = string_t(trim (arguments(i)))
82
+ end do
83
+
84
+ end function cct_new
85
+
60
86
! > Cleanup compile command
61
87
elemental subroutine compile_command_destroy (self )
62
88
@@ -281,10 +307,9 @@ subroutine cct_register(self, command, target_os, error)
281
307
! Fallback: use last argument if not found
282
308
if (len_trim (source_file)==0 ) source_file = trim (args(n))
283
309
284
- ! Fill in the compile_command_t
285
- cmd = compile_command_t(directory = string_t(cwd), &
286
- arguments = [(string_t(trim (args(i))), i= 1 ,n)], &
287
- file = string_t(source_file))
310
+ ! Fill in the compile_command_t.
311
+ ! Use non-default initializer due to gcc 15 bug
312
+ cmd = compile_command_t(cwd, args, source_file)
288
313
289
314
! Add it to the structure
290
315
! $omp critical (command_update)
0 commit comments