Skip to content

Commit 96095dd

Browse files
authored
Merge branch 'master' into incremental2
2 parents a16a2b7 + c4ce73e commit 96095dd

File tree

10 files changed

+174
-162
lines changed

10 files changed

+174
-162
lines changed

fpm/src/fpm.f90

Lines changed: 19 additions & 55 deletions
Original file line numberDiff line numberDiff line change
@@ -13,14 +13,13 @@ module fpm
1313
use fpm_sources, only: add_executable_sources, add_sources_from_dir
1414
use fpm_targets, only: targets_from_sources, resolve_module_dependencies, &
1515
resolve_target_linking
16-
use fpm_manifest, only : get_package_data, default_executable, &
17-
default_library, package_t, default_test
16+
use fpm_manifest, only : get_package_data, package_config_t
1817
use fpm_error, only : error_t, fatal_error
19-
use fpm_manifest_test, only : test_t
18+
use fpm_manifest_test, only : test_config_t
2019
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
2120
& stdout=>output_unit, &
2221
& stderr=>error_unit
23-
use fpm_manifest_dependency, only: dependency_t
22+
use fpm_manifest_dependency, only: dependency_config_t
2423
implicit none
2524
private
2625
public :: cmd_build, cmd_install, cmd_run
@@ -35,7 +34,7 @@ recursive subroutine add_libsources_from_package(sources,link_libraries,package_
3534
type(srcfile_t), allocatable, intent(inout), target :: sources(:)
3635
type(string_t), allocatable, intent(inout) :: link_libraries(:)
3736
type(string_t), allocatable, intent(inout) :: package_list(:)
38-
type(package_t), intent(in) :: package
37+
type(package_config_t), intent(in) :: package
3938
character(*), intent(in) :: package_root
4039
logical, intent(in) :: dev_depends
4140
type(error_t), allocatable, intent(out) :: error
@@ -77,11 +76,11 @@ recursive subroutine add_libsources_from_package(sources,link_libraries,package_
7776
contains
7877

7978
subroutine add_dependencies(dependency_list)
80-
type(dependency_t), intent(in) :: dependency_list(:)
79+
type(dependency_config_t), intent(in) :: dependency_list(:)
8180

8281
integer :: i
8382
type(string_t) :: dep_name
84-
type(package_t) :: dependency
83+
type(package_config_t) :: dependency
8584

8685
character(:), allocatable :: dependency_path
8786

@@ -136,8 +135,8 @@ subroutine add_dependencies(dependency_list)
136135

137136
dep_name%s = dependency_list(i)%name
138137
package_list = [package_list, dep_name]
139-
if (allocated(dependency%build_config%link)) then
140-
link_libraries = [link_libraries, dependency%build_config%link]
138+
if (allocated(dependency%build%link)) then
139+
link_libraries = [link_libraries, dependency%build%link]
141140
end if
142141

143142
end do
@@ -152,15 +151,15 @@ subroutine build_model(model, settings, package, error)
152151
!
153152
type(fpm_model_t), intent(out) :: model
154153
type(fpm_build_settings), intent(in) :: settings
155-
type(package_t), intent(in) :: package
154+
type(package_config_t), intent(in) :: package
156155
type(error_t), allocatable, intent(out) :: error
157156

158157
integer :: i
159158
type(string_t), allocatable :: package_list(:)
160159

161160
model%package_name = package%name
162-
if (allocated(package%build_config%link)) then
163-
model%link_libraries = package%build_config%link
161+
if (allocated(package%build%link)) then
162+
model%link_libraries = package%build%link
164163
else
165164
allocate(model%link_libraries(0))
166165
end if
@@ -190,7 +189,7 @@ subroutine build_model(model, settings, package, error)
190189
model%link_flags = ''
191190

192191
! Add sources from executable directories
193-
if (is_dir('app') .and. package%build_config%auto_executables) then
192+
if (is_dir('app') .and. package%build%auto_executables) then
194193
call add_sources_from_dir(model%sources,'app', FPM_SCOPE_APP, &
195194
with_executables=.true., error=error)
196195

@@ -199,7 +198,7 @@ subroutine build_model(model, settings, package, error)
199198
end if
200199

201200
end if
202-
if (is_dir('test') .and. package%build_config%auto_tests) then
201+
if (is_dir('test') .and. package%build%auto_tests) then
203202
call add_sources_from_dir(model%sources,'test', FPM_SCOPE_TEST, &
204203
with_executables=.true., error=error)
205204

@@ -210,7 +209,7 @@ subroutine build_model(model, settings, package, error)
210209
end if
211210
if (allocated(package%executable)) then
212211
call add_executable_sources(model%sources, package%executable, FPM_SCOPE_APP, &
213-
auto_discover=package%build_config%auto_executables, &
212+
auto_discover=package%build%auto_executables, &
214213
error=error)
215214

216215
if (allocated(error)) then
@@ -220,7 +219,7 @@ subroutine build_model(model, settings, package, error)
220219
end if
221220
if (allocated(package%test)) then
222221
call add_executable_sources(model%sources, package%test, FPM_SCOPE_TEST, &
223-
auto_discover=package%build_config%auto_tests, &
222+
auto_discover=package%build%auto_tests, &
224223
error=error)
225224

226225
if (allocated(error)) then
@@ -252,53 +251,21 @@ subroutine build_model(model, settings, package, error)
252251

253252
end subroutine build_model
254253

255-
!> Apply package defaults
256-
subroutine package_defaults(package)
257-
type(package_t), intent(inout) :: package
258-
259-
! Populate library in case we find the default src directory
260-
if (.not.allocated(package%library) .and. exists("src")) then
261-
allocate(package%library)
262-
call default_library(package%library)
263-
end if
264-
265-
! Populate executable in case we find the default app
266-
if (.not.allocated(package%executable) .and. &
267-
exists(join_path('app',"main.f90"))) then
268-
allocate(package%executable(1))
269-
call default_executable(package%executable(1), package%name)
270-
end if
271-
272-
! Populate test in case we find the default test directory
273-
if (.not.allocated(package%test) .and. &
274-
exists(join_path("test","main.f90"))) then
275-
allocate(package%test(1))
276-
call default_test(package%test(1), package%name)
277-
endif
278-
279-
if (.not.(allocated(package%library) .or. allocated(package%executable))) then
280-
print '(a)', "Neither library nor executable found, there is nothing to do"
281-
error stop 1
282-
end if
283-
284-
end subroutine
285254

286255
subroutine cmd_build(settings)
287256
type(fpm_build_settings), intent(in) :: settings
288-
type(package_t) :: package
257+
type(package_config_t) :: package
289258
type(fpm_model_t) :: model
290259
type(error_t), allocatable :: error
291260

292261
integer :: i
293262

294-
call get_package_data(package, "fpm.toml", error)
263+
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
295264
if (allocated(error)) then
296265
print '(a)', error%message
297266
error stop 1
298267
end if
299268

300-
call package_defaults(package)
301-
302269
call build_model(model, settings, package, error)
303270
if (allocated(error)) then
304271
print '(a)', error%message
@@ -329,22 +296,19 @@ subroutine cmd_run(settings,test)
329296
integer :: i, j, col_width, nCol
330297
logical :: found(size(settings%name))
331298
type(error_t), allocatable :: error
332-
type(package_t) :: package
299+
type(package_config_t) :: package
333300
type(fpm_model_t) :: model
334301
type(string_t) :: exe_cmd
335302
type(string_t), allocatable :: executables(:)
336303
type(build_target_t), pointer :: exe_target
337304
type(srcfile_t), pointer :: exe_source
338305

339-
call get_package_data(package, "fpm.toml", error)
306+
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
340307
if (allocated(error)) then
341308
print '(a)', error%message
342309
error stop 1
343310
end if
344311

345-
346-
call package_defaults(package)
347-
348312
call build_model(model, settings%fpm_build_settings, package, error)
349313
if (allocated(error)) then
350314
print '(a)', error%message

fpm/src/fpm/manifest.f90

Lines changed: 59 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -7,18 +7,19 @@
77
!> Additionally, the required data types for users of this module are reexported
88
!> to hide the actual implementation details.
99
module fpm_manifest
10-
use fpm_manifest_build_config, only: build_config_t
11-
use fpm_manifest_executable, only : executable_t
12-
use fpm_manifest_library, only : library_t
13-
use fpm_manifest_package, only : package_t, new_package
10+
use fpm_manifest_build, only: build_config_t
11+
use fpm_manifest_executable, only : executable_config_t
12+
use fpm_manifest_library, only : library_config_t
13+
use fpm_manifest_package, only : package_config_t, new_package
1414
use fpm_error, only : error_t, fatal_error, file_not_found_error
1515
use fpm_toml, only : toml_table, read_package_file
16-
use fpm_manifest_test, only : test_t
16+
use fpm_manifest_test, only : test_config_t
17+
use fpm_filesystem, only: join_path, exists
1718
implicit none
1819
private
1920

2021
public :: get_package_data, default_executable, default_library, default_test
21-
public :: package_t
22+
public :: package_config_t
2223

2324

2425
contains
@@ -28,7 +29,7 @@ module fpm_manifest
2829
subroutine default_library(self)
2930

3031
!> Instance of the library meta data
31-
type(library_t), intent(out) :: self
32+
type(library_config_t), intent(out) :: self
3233

3334
self%source_dir = "src"
3435

@@ -39,7 +40,7 @@ end subroutine default_library
3940
subroutine default_executable(self, name)
4041

4142
!> Instance of the executable meta data
42-
type(executable_t), intent(out) :: self
43+
type(executable_config_t), intent(out) :: self
4344

4445
!> Name of the package
4546
character(len=*), intent(in) :: name
@@ -54,7 +55,7 @@ end subroutine default_executable
5455
subroutine default_test(self, name)
5556

5657
!> Instance of the executable meta data
57-
type(test_t), intent(out) :: self
58+
type(test_config_t), intent(out) :: self
5859

5960
!> Name of the package
6061
character(len=*), intent(in) :: name
@@ -67,17 +68,20 @@ end subroutine default_test
6768

6869

6970
!> Obtain package meta data from a configuation file
70-
subroutine get_package_data(package, file, error)
71+
subroutine get_package_data(package, file, error, apply_defaults)
7172

7273
!> Parsed package meta data
73-
type(package_t), intent(out) :: package
74+
type(package_config_t), intent(out) :: package
7475

7576
!> Name of the package configuration file
7677
character(len=*), intent(in) :: file
7778

7879
!> Error status of the operation
7980
type(error_t), allocatable, intent(out) :: error
8081

82+
!> Apply package defaults (uses file system operations)
83+
logical, intent(in), optional :: apply_defaults
84+
8185
type(toml_table), allocatable :: table
8286

8387
call read_package_file(table, file, error)
@@ -90,7 +94,51 @@ subroutine get_package_data(package, file, error)
9094

9195
call new_package(package, table, error)
9296

97+
if (present(apply_defaults)) then
98+
if (apply_defaults) then
99+
call package_defaults(package, error)
100+
if (allocated(error)) return
101+
end if
102+
end if
103+
93104
end subroutine get_package_data
94105

95106

107+
!> Apply package defaults
108+
subroutine package_defaults(package, error)
109+
110+
!> Parsed package meta data
111+
type(package_config_t), intent(inout) :: package
112+
113+
!> Error status of the operation
114+
type(error_t), allocatable, intent(out) :: error
115+
116+
! Populate library in case we find the default src directory
117+
if (.not.allocated(package%library) .and. exists("src")) then
118+
allocate(package%library)
119+
call default_library(package%library)
120+
end if
121+
122+
! Populate executable in case we find the default app
123+
if (.not.allocated(package%executable) .and. &
124+
exists(join_path('app',"main.f90"))) then
125+
allocate(package%executable(1))
126+
call default_executable(package%executable(1), package%name)
127+
end if
128+
129+
! Populate test in case we find the default test directory
130+
if (.not.allocated(package%test) .and. &
131+
exists(join_path("test","main.f90"))) then
132+
allocate(package%test(1))
133+
call default_test(package%test(1), package%name)
134+
endif
135+
136+
if (.not.(allocated(package%library) .or. allocated(package%executable))) then
137+
call fatal_error(error, "Neither library nor executable found, there is nothing to do")
138+
return
139+
end if
140+
141+
end subroutine package_defaults
142+
143+
96144
end module fpm_manifest

fpm/src/fpm/manifest/build_config.f90 renamed to fpm/src/fpm/manifest/build.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@
88
!>auto-tests = bool
99
!>link = ["lib"]
1010
!>```
11-
module fpm_manifest_build_config
11+
module fpm_manifest_build
1212
use fpm_error, only : error_t, syntax_error, fatal_error
1313
use fpm_strings, only : string_t
1414
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
@@ -146,4 +146,4 @@ subroutine info(self, unit, verbosity)
146146

147147
end subroutine info
148148

149-
end module fpm_manifest_build_config
149+
end module fpm_manifest_build

fpm/src/fpm/manifest/dependency.f90

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -30,11 +30,11 @@ module fpm_manifest_dependency
3030
implicit none
3131
private
3232

33-
public :: dependency_t, new_dependency, new_dependencies
33+
public :: dependency_config_t, new_dependency, new_dependencies
3434

3535

3636
!> Configuration meta data for a dependency
37-
type :: dependency_t
37+
type :: dependency_config_t
3838

3939
!> Name of the dependency
4040
character(len=:), allocatable :: name
@@ -50,7 +50,7 @@ module fpm_manifest_dependency
5050
!> Print information on this instance
5151
procedure :: info
5252

53-
end type dependency_t
53+
end type dependency_config_t
5454

5555

5656
contains
@@ -60,7 +60,7 @@ module fpm_manifest_dependency
6060
subroutine new_dependency(self, table, error)
6161

6262
!> Instance of the dependency configuration
63-
type(dependency_t), intent(out) :: self
63+
type(dependency_config_t), intent(out) :: self
6464

6565
!> Instance of the TOML data structure
6666
type(toml_table), intent(inout) :: table
@@ -176,7 +176,7 @@ end subroutine check
176176
subroutine new_dependencies(deps, table, error)
177177

178178
!> Instance of the dependency configuration
179-
type(dependency_t), allocatable, intent(out) :: deps(:)
179+
type(dependency_config_t), allocatable, intent(out) :: deps(:)
180180

181181
!> Instance of the TOML data structure
182182
type(toml_table), intent(inout) :: table
@@ -210,7 +210,7 @@ end subroutine new_dependencies
210210
subroutine info(self, unit, verbosity)
211211

212212
!> Instance of the dependency configuration
213-
class(dependency_t), intent(in) :: self
213+
class(dependency_config_t), intent(in) :: self
214214

215215
!> Unit for IO
216216
integer, intent(in) :: unit

0 commit comments

Comments
 (0)