Skip to content

Commit fd1c609

Browse files
committed
custom OS type
1 parent 51fe318 commit fd1c609

File tree

3 files changed

+9
-6
lines changed

3 files changed

+9
-6
lines changed

src/fpm_compile_commands.F90

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -226,14 +226,17 @@ elemental subroutine cct_destroy(self)
226226
end subroutine cct_destroy
227227

228228
!> Register a new compile command
229-
subroutine cct_register(self, command, error)
229+
subroutine cct_register(self, command, target_os, error)
230230

231231
!> Instance of the serializable object
232232
class(compile_command_table_t), intent(inout) :: self
233233

234234
!> Data structure
235235
character(len=*), intent(in) :: command
236236

237+
!> The target OS of the compile_commands.json (may be cross-compiling)
238+
integer, intent(in) :: target_os
239+
237240
!> Error handling
238241
type(error_t), allocatable, intent(out) :: error
239242

@@ -250,7 +253,7 @@ subroutine cct_register(self, command, error)
250253
end if
251254

252255
! Tokenize the input command into args(:)
253-
if (get_os_type()==OS_WINDOWS) then
256+
if (target_os==OS_WINDOWS) then
254257
args = ms_split(command, ucrt=.true., success=sh_success)
255258
else
256259
args = sh_split(command, join_spaced=.false., keep_quotes=.true., success=sh_success)

src/fpm_compiler.F90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1141,7 +1141,7 @@ subroutine compile_fortran(self, input, output, args, log_file, stat, table, dry
11411141

11421142
! Optionally register compile command
11431143
if (present(table)) then
1144-
call table%register(command, error)
1144+
call table%register(command, get_os_type(), error)
11451145
stat = merge(-1,0,allocated(error))
11461146
endif
11471147

@@ -1186,7 +1186,7 @@ subroutine compile_c(self, input, output, args, log_file, stat, table, dry_run)
11861186

11871187
! Optionally register compile command
11881188
if (present(table)) then
1189-
call table%register(command, error)
1189+
call table%register(command, get_os_type(), error)
11901190
stat = merge(-1,0,allocated(error))
11911191
endif
11921192

@@ -1230,7 +1230,7 @@ subroutine compile_cpp(self, input, output, args, log_file, stat, table, dry_run
12301230

12311231
! Optionally register compile command
12321232
if (present(table)) then
1233-
call table%register(command, error)
1233+
call table%register(command, get_os_type(), error)
12341234
stat = merge(-1,0,allocated(error))
12351235
endif
12361236

src/fpm_targets.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -908,7 +908,7 @@ subroutine resolve_target_linking(targets, model)
908908

909909
target%output_dir = get_output_dir(model%build_prefix, &
910910
& target%compile_flags//local_link_flags)
911-
target%output_file = join_path(target%output_dir, target%output_name)
911+
target%output_file = join_path(target%output_dir, target%output_name)
912912
target%output_log_file = join_path(target%output_dir, target%output_name)//'.log'
913913
end if
914914

0 commit comments

Comments
 (0)