@@ -6,7 +6,7 @@ module fpm_sources
6
6
FPM_UNIT_CSOURCE, FPM_UNIT_CHEADER, FPM_SCOPE_UNKNOWN, &
7
7
FPM_SCOPE_LIB, FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST
8
8
9
- use fpm_filesystem, only: basename, canon_path, dirname, read_lines, list_files
9
+ use fpm_filesystem, only: basename, canon_path, dirname, join_path, read_lines, list_files
10
10
use fpm_strings, only: lower, split, str_ends_with, string_t, operator (.in .)
11
11
use fpm_manifest_executable, only: executable_t
12
12
implicit none
@@ -24,6 +24,33 @@ module fpm_sources
24
24
25
25
contains
26
26
27
+ function parse_source (source_file_path ,error ) result(source)
28
+ character (* ), intent (in ) :: source_file_path
29
+ type (error_t), allocatable , intent (out ) :: error
30
+ type (srcfile_t) :: source
31
+
32
+ if (str_ends_with(lower(source_file_path), " .f90" )) then
33
+
34
+ source = parse_f_source(source_file_path, error)
35
+
36
+ if (source% unit_type == FPM_UNIT_PROGRAM) then
37
+ source% exe_name = basename(source_file_path,suffix= .false. )
38
+ end if
39
+
40
+ else if (str_ends_with(lower(source_file_path), " .c" ) .or. &
41
+ str_ends_with(lower(source_file_path), " .h" )) then
42
+
43
+ source = parse_c_source(source_file_path,error)
44
+
45
+ end if
46
+
47
+ if (allocated (error)) then
48
+ return
49
+ end if
50
+
51
+ end function parse_source
52
+
53
+
27
54
subroutine add_sources_from_dir (sources ,directory ,scope ,with_executables ,error )
28
55
! Enumerate sources in a directory
29
56
!
@@ -33,7 +60,7 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,error)
33
60
logical , intent (in ), optional :: with_executables
34
61
type (error_t), allocatable , intent (out ) :: error
35
62
36
- integer :: i, j
63
+ integer :: i
37
64
logical , allocatable :: is_source(:), exclude_source(:)
38
65
type (string_t), allocatable :: file_names(:)
39
66
type (string_t), allocatable :: src_file_names(:)
@@ -46,13 +73,13 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,error)
46
73
if (allocated (sources)) then
47
74
allocate (existing_src_files(size (sources)))
48
75
do i= 1 ,size (sources)
49
- existing_src_files(i)% s = sources(i)% file_name
76
+ existing_src_files(i)% s = canon_path( sources(i)% file_name)
50
77
end do
51
78
else
52
79
allocate (existing_src_files(0 ))
53
80
end if
54
81
55
- is_source = [(.not. (file_names(i)% s .in . existing_src_files) .and. &
82
+ is_source = [(.not. (canon_path( file_names(i)% s) .in . existing_src_files) .and. &
56
83
(str_ends_with(lower(file_names(i)% s), " .f90" ) .or. &
57
84
str_ends_with(lower(file_names(i)% s), " .c" ) .or. &
58
85
str_ends_with(lower(file_names(i)% s), " .h" ) ),i= 1 ,size (file_names))]
@@ -63,26 +90,8 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,error)
63
90
64
91
do i = 1 , size (src_file_names)
65
92
66
- if (str_ends_with(lower(src_file_names(i)% s), " .f90" )) then
67
-
68
- dir_sources(i) = parse_f_source(src_file_names(i)% s, error)
69
-
70
- if (allocated (error)) then
71
- return
72
- end if
73
-
74
- end if
75
-
76
- if (str_ends_with(lower(src_file_names(i)% s), " .c" ) .or. &
77
- str_ends_with(lower(src_file_names(i)% s), " .h" )) then
78
-
79
- dir_sources(i) = parse_c_source(src_file_names(i)% s,error)
80
-
81
- if (allocated (error)) then
82
- return
83
- end if
84
-
85
- end if
93
+ dir_sources(i) = parse_source(src_file_names(i)% s,error)
94
+ if (allocated (error)) return
86
95
87
96
dir_sources(i)% unit_scope = scope
88
97
@@ -93,7 +102,6 @@ subroutine add_sources_from_dir(sources,directory,scope,with_executables,error)
93
102
if (with_executables) then
94
103
95
104
exclude_source(i) = .false.
96
- dir_sources(i)% exe_name = basename(src_file_names(i)% s,suffix= .false. )
97
105
98
106
end if
99
107
end if
@@ -122,49 +130,50 @@ subroutine add_executable_sources(sources,executables,scope,auto_discover,error)
122
130
integer :: i, j
123
131
124
132
type (string_t), allocatable :: exe_dirs(:)
125
- logical , allocatable :: include_source(:)
126
- type (srcfile_t), allocatable :: dir_sources(:)
133
+ type (srcfile_t) :: exe_source
127
134
128
135
call get_executable_source_dirs(exe_dirs,executables)
129
136
130
137
do i= 1 ,size (exe_dirs)
131
- call add_sources_from_dir(dir_sources ,exe_dirs(i)% s, &
132
- scope, with_executables= .true. ,error= error)
138
+ call add_sources_from_dir(sources ,exe_dirs(i)% s, &
139
+ scope, with_executables= auto_discover ,error= error)
133
140
134
141
if (allocated (error)) then
135
142
return
136
143
end if
137
144
end do
138
145
139
- allocate (include_source( size (dir_sources)) )
146
+ exe_loop: do i = 1 , size (executables )
140
147
141
- do i = 1 , size (dir_sources)
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
148
- do j= 1 ,size (executables)
148
+ ! Check if executable already discovered automatically
149
+ ! and apply any overrides
150
+ do j= 1 ,size (sources)
149
151
150
- if (basename(dir_sources(i )% file_name,suffix= .true. ) == executables(j )% main .and. &
151
- canon_path(dirname(dir_sources(i )% file_name)) == &
152
- canon_path(executables(j )% source_dir) ) then
152
+ if (basename(sources(j )% file_name,suffix= .true. ) == executables(i )% main .and. &
153
+ canon_path(dirname(sources(j )% file_name)) == &
154
+ canon_path(executables(i )% source_dir) ) then
153
155
154
- include_source(i) = .true.
155
- dir_sources(i)% exe_name = executables(j)% name
156
- exit
156
+ sources(j)% exe_name = executables(i)% name
157
+ cycle exe_loop
157
158
158
159
end if
160
+
159
161
end do
160
162
161
- end do
163
+ ! Add if not already discovered (auto_discovery off)
164
+ exe_source = parse_source(join_path(executables(i)% source_dir,executables(i)% main),error)
165
+ exe_source% exe_name = executables(i)% name
166
+ exe_source% unit_scope = scope
167
+
168
+ if (allocated (error)) return
162
169
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
170
+ if (.not. allocated (sources)) then
171
+ sources = [exe_source]
172
+ else
173
+ sources = [sources, exe_source]
174
+ end if
175
+
176
+ end do exe_loop
168
177
169
178
end subroutine add_executable_sources
170
179
0 commit comments