Skip to content

Commit 54dcbc1

Browse files
committed
Update: to match bootstrap fpm object file naming
Include relative path components in target object filenames to avoid collisions due to sources with the same name but in different directories.
1 parent 0308cf5 commit 54dcbc1

File tree

1 file changed

+39
-3
lines changed

1 file changed

+39
-3
lines changed

fpm/src/fpm_backend.f90

Lines changed: 39 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@ module fpm_backend
22

33
! Implements the native fpm build backend
44

5-
use fpm_environment, only: run
5+
use fpm_environment, only: run, get_os_type, OS_WINDOWS
66
use fpm_filesystem, only: basename, join_path, exists, mkdir
77
use fpm_model, only: fpm_model_t, srcfile_t, FPM_UNIT_MODULE, &
88
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
@@ -109,8 +109,7 @@ recursive subroutine build_source(model,source_file,linking)
109109

110110
end do
111111

112-
object_file = join_path(model%output_directory, model%package_name, &
113-
basename(source_file%file_name,suffix=.false.)//'.o')
112+
object_file = get_object_name(model,source_file%file_name)
114113

115114
call run("gfortran -c " // source_file%file_name // model%fortran_compile_flags &
116115
// " -o " // object_file)
@@ -120,4 +119,41 @@ recursive subroutine build_source(model,source_file,linking)
120119

121120
end subroutine build_source
122121

122+
123+
function get_object_name(model,source_file_name) result(object_file)
124+
! Generate object target path from source name and model params
125+
!
126+
! src/test.f90 -> <output-dir>/<package-name>/test.o
127+
! src/subdir/test.f90 -> <output-dir>/<package-name>/subdir_test.o
128+
!
129+
type(fpm_model_t), intent(in) :: model
130+
character(*), intent(in) :: source_file_name
131+
character(:), allocatable :: object_file
132+
133+
integer :: i
134+
character(1) :: filesep
135+
136+
select case(get_os_type())
137+
case (OS_WINDOWS)
138+
filesep = '\'
139+
case default
140+
filesep = '/'
141+
end select
142+
143+
! Exclude first directory level from path
144+
object_file = source_file_name(index(source_file_name,filesep)+1:)
145+
146+
! Convert remaining directory separators to underscores
147+
i = index(object_file,filesep)
148+
do while(i > 0)
149+
object_file(i:i) = '_'
150+
i = index(object_file,filesep)
151+
end do
152+
153+
! Construct full target path
154+
object_file = join_path(model%output_directory, model%package_name, &
155+
basename(object_file,suffix=.false.)//'.o')
156+
157+
end function get_object_name
158+
123159
end module fpm_backend

0 commit comments

Comments
 (0)