@@ -109,45 +109,63 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,error)
109
109
end subroutine add_sources_from_dir
110
110
111
111
112
- subroutine add_executable_sources (sources ,executables ,scope ,error )
112
+ subroutine add_executable_sources (sources ,executables ,scope ,auto_discover , error )
113
113
! Include sources from any directories specified
114
114
! in [[executable]] entries and apply any customisations
115
115
!
116
116
type (srcfile_t), allocatable , intent (inout ), target :: sources(:)
117
117
class(executable_t), intent (in ) :: executables(:)
118
118
integer , intent (in ) :: scope
119
+ logical , intent (in ) :: auto_discover
119
120
type (error_t), allocatable , intent (out ) :: error
120
121
121
122
integer :: i, j
122
123
123
124
type (string_t), allocatable :: exe_dirs(:)
125
+ logical , allocatable :: include_source(:)
126
+ type (srcfile_t), allocatable :: dir_sources(:)
124
127
125
128
call get_executable_source_dirs(exe_dirs,executables)
126
129
127
130
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, &
129
132
scope, with_executables= .true. ,error= error)
130
133
131
134
if (allocated (error)) then
132
135
return
133
136
end if
134
137
end do
135
138
136
- do i = 1 , size (sources)
139
+ allocate (include_source(size (dir_sources)))
140
+
141
+ do i = 1 , size (dir_sources)
137
142
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
138
148
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)) == &
142
152
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
145
156
exit
157
+
146
158
end if
147
159
end do
148
160
149
161
end do
150
162
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
+
151
169
end subroutine add_executable_sources
152
170
153
171
0 commit comments