Skip to content

Commit f10b174

Browse files
committed
Add: source-level flag to enable/disable auto-discovery
1 parent c058c12 commit f10b174

File tree

2 files changed

+28
-10
lines changed

2 files changed

+28
-10
lines changed

fpm/src/fpm.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -77,7 +77,7 @@ subroutine build_model(model, settings, package, error)
7777
end if
7878
if (allocated(package%executable)) then
7979
call add_executable_sources(model%sources, package%executable, &
80-
FPM_SCOPE_APP, error=error)
80+
FPM_SCOPE_APP, auto_discover=.true., error=error)
8181

8282
if (allocated(error)) then
8383
return
@@ -86,7 +86,7 @@ subroutine build_model(model, settings, package, error)
8686
end if
8787
if (allocated(package%test)) then
8888
call add_executable_sources(model%sources, package%test, &
89-
FPM_SCOPE_TEST, error=error)
89+
FPM_SCOPE_TEST, auto_discover=.true., error=error)
9090

9191
if (allocated(error)) then
9292
return

fpm/src/fpm_sources.f90

Lines changed: 26 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -109,45 +109,63 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,error)
109109
end subroutine add_sources_from_dir
110110

111111

112-
subroutine add_executable_sources(sources,executables,scope,error)
112+
subroutine add_executable_sources(sources,executables,scope,auto_discover,error)
113113
! Include sources from any directories specified
114114
! in [[executable]] entries and apply any customisations
115115
!
116116
type(srcfile_t), allocatable, intent(inout), target :: sources(:)
117117
class(executable_t), intent(in) :: executables(:)
118118
integer, intent(in) :: scope
119+
logical, intent(in) :: auto_discover
119120
type(error_t), allocatable, intent(out) :: error
120121

121122
integer :: i, j
122123

123124
type(string_t), allocatable :: exe_dirs(:)
125+
logical, allocatable :: include_source(:)
126+
type(srcfile_t), allocatable :: dir_sources(:)
124127

125128
call get_executable_source_dirs(exe_dirs,executables)
126129

127130
do i=1,size(exe_dirs)
128-
call add_sources_from_dir(sources,exe_dirs(i)%s, &
131+
call add_sources_from_dir(dir_sources,exe_dirs(i)%s, &
129132
scope, with_executables=.true.,error=error)
130133

131134
if (allocated(error)) then
132135
return
133136
end if
134137
end do
135138

136-
do i = 1, size(sources)
139+
allocate(include_source(size(dir_sources)))
140+
141+
do i = 1, size(dir_sources)
137142

143+
! Include source by default if not a program or if auto_discover is enabled
144+
include_source(i) = (dir_sources(i)%unit_type /= FPM_UNIT_PROGRAM) .or. &
145+
auto_discover
146+
147+
! Always include sources specified in fpm.toml
138148
do j=1,size(executables)
139-
if (basename(sources(i)%file_name,suffix=.true.) == &
140-
if (basename(sources(i)%file_name,suffix=.true.) == executables(j)%main .and.&
141-
canon_path(dirname(sources(i)%file_name)) == &
149+
150+
if (basename(dir_sources(i)%file_name,suffix=.true.) == executables(j)%main .and.&
151+
canon_path(dirname(dir_sources(i)%file_name)) == &
142152
canon_path(executables(j)%source_dir) ) then
143-
144-
sources(i)%exe_name = executables(j)%name
153+
154+
include_source(i) = .true.
155+
dir_sources(i)%exe_name = executables(j)%name
145156
exit
157+
146158
end if
147159
end do
148160

149161
end do
150162

163+
if (.not.allocated(sources)) then
164+
sources = pack(dir_sources,include_source)
165+
else
166+
sources = [sources, pack(dir_sources,include_source)]
167+
end if
168+
151169
end subroutine add_executable_sources
152170

153171

0 commit comments

Comments
 (0)