Skip to content

Commit eaf7748

Browse files
committed
Implement example applications in Fortran fpm
1 parent d398f1c commit eaf7748

File tree

15 files changed

+378
-20
lines changed

15 files changed

+378
-20
lines changed

ci/run_tests.bat

Lines changed: 12 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -103,6 +103,17 @@ if errorlevel 1 exit 1
103103
.\build\gfortran_debug\test\farewell_test
104104

105105

106+
cd ..\with_examples
107+
if errorlevel 1 exit 1
108+
109+
del /q /f build
110+
%fpm_path% build
111+
if errorlevel 1 exit 1
112+
113+
.\build\gfortran_debug\app\demo-prog
114+
if errorlevel 1 exit 1
115+
116+
106117
cd ..\auto_discovery_off
107118
if errorlevel 1 exit 1
108119

@@ -161,4 +172,4 @@ if errorlevel 1 exit 1
161172
.\build\gfortran_debug\app\gomp_test
162173
if errorlevel 1 exit 1
163174

164-
cd ..\..
175+
cd ..\..

ci/run_tests.sh

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -48,6 +48,10 @@ cd ../hello_complex_2
4848
./build/gfortran_debug/test/greet_test
4949
./build/gfortran_debug/test/farewell_test
5050

51+
cd ../with_examples
52+
"${f_fpm_path}" build
53+
./build/gfortran_debug/app/demo-prog
54+
5155
cd ../auto_discovery_off
5256
"${f_fpm_path}" build
5357
./build/gfortran_debug/app/auto_discovery_off
@@ -75,4 +79,4 @@ cd ../link_executable
7579
./build/gfortran_debug/app/gomp_test
7680

7781
# Cleanup
78-
rm -rf ./*/build
82+
rm -rf ./*/build

example_packages/README.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@ the features demonstrated in each package and which versions of fpm are supporte
1313
| hello_complex_2 | Auto-discovery of tests and executables with modules | N | Y |
1414
| hello_fpm | App-only; local path dependency | Y | Y |
1515
| hello_world | App-only | Y | Y |
16+
| with_examples | Example-only | N | Y |
1617
| makefile_complex | External build command (makefile); local path dependency | Y | N |
1718
| program_with_module | App-only; module+program in single source file | Y | Y |
1819
| submodules | Lib-only; submodules (3 levels) | N | Y |
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
/build/*
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
program demo
2+
write(*, '(a)') "This is a simple demo program, but not a real application"
3+
end program demo
Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
name = "with_examples"
2+
build.auto-examples = false
3+
4+
[[example]]
5+
name = "demo-prog"
6+
source-dir = "demo"
7+
main = "prog.f90"

fpm/src/fpm.f90

Lines changed: 30 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -6,8 +6,8 @@ module fpm
66
use fpm_environment, only: run
77
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
88
use fpm_model, only: fpm_model_t, srcfile_t, build_target_t, &
9-
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
10-
FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST, &
9+
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
10+
FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST, &
1111
FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE
1212
use fpm_compiler, only: add_compile_flag_defaults
1313

@@ -196,6 +196,15 @@ subroutine build_model(model, settings, package, error)
196196
return
197197
end if
198198

199+
end if
200+
if (is_dir('example') .and. package%build%auto_examples) then
201+
call add_sources_from_dir(model%sources,'example', FPM_SCOPE_EXAMPLE, &
202+
with_executables=.true., error=error)
203+
204+
if (allocated(error)) then
205+
return
206+
end if
207+
199208
end if
200209
if (is_dir('test') .and. package%build%auto_tests) then
201210
call add_sources_from_dir(model%sources,'test', FPM_SCOPE_TEST, &
@@ -215,6 +224,16 @@ subroutine build_model(model, settings, package, error)
215224
return
216225
end if
217226

227+
end if
228+
if (allocated(package%example)) then
229+
call add_executable_sources(model%sources, package%example, FPM_SCOPE_EXAMPLE, &
230+
auto_discover=package%build%auto_executables, &
231+
error=error)
232+
233+
if (allocated(error)) then
234+
return
235+
end if
236+
218237
end if
219238
if (allocated(package%test)) then
220239
call add_executable_sources(model%sources, package%test, FPM_SCOPE_TEST, &
@@ -301,6 +320,7 @@ subroutine cmd_run(settings,test)
301320
type(string_t), allocatable :: executables(:)
302321
type(build_target_t), pointer :: exe_target
303322
type(srcfile_t), pointer :: exe_source
323+
integer :: run_scope
304324

305325
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
306326
if (allocated(error)) then
@@ -314,6 +334,12 @@ subroutine cmd_run(settings,test)
314334
error stop 1
315335
end if
316336

337+
if (test) then
338+
run_scope = FPM_SCOPE_TEST
339+
else
340+
run_scope = merge(FPM_SCOPE_EXAMPLE, FPM_SCOPE_APP, settings%example)
341+
end if
342+
317343
! Enumerate executable targets to run
318344
col_width = -1
319345
found(:) = .false.
@@ -327,8 +353,7 @@ subroutine cmd_run(settings,test)
327353

328354
exe_source => exe_target%dependencies(1)%ptr%source
329355

330-
if (exe_source%unit_scope == &
331-
merge(FPM_SCOPE_TEST,FPM_SCOPE_APP,test)) then
356+
if (exe_source%unit_scope == run_scope) then
332357

333358
col_width = max(col_width,len(basename(exe_target%output_file))+2)
334359

@@ -391,8 +416,7 @@ subroutine cmd_run(settings,test)
391416

392417
exe_source => exe_target%dependencies(1)%ptr%source
393418

394-
if (exe_source%unit_scope == &
395-
merge(FPM_SCOPE_TEST,FPM_SCOPE_APP,test)) then
419+
if (exe_source%unit_scope == run_scope) then
396420

397421
write(stderr,'(A)',advance=(merge("yes","no ",modulo(j,nCol)==0))) &
398422
& [character(len=col_width) :: basename(exe_target%output_file)]

fpm/src/fpm/manifest.f90

Lines changed: 28 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@
88
!> to hide the actual implementation details.
99
module fpm_manifest
1010
use fpm_manifest_build, only: build_config_t
11+
use fpm_manifest_example, only : example_config_t
1112
use fpm_manifest_executable, only : executable_config_t
1213
use fpm_manifest_library, only : library_config_t
1314
use fpm_manifest_package, only : package_config_t, new_package
@@ -19,6 +20,7 @@ module fpm_manifest
1920
private
2021

2122
public :: get_package_data, default_executable, default_library, default_test
23+
public :: default_example
2224
public :: package_config_t
2325

2426

@@ -51,6 +53,21 @@ subroutine default_executable(self, name)
5153

5254
end subroutine default_executable
5355

56+
!> Populate test in case we find the default example/ directory
57+
subroutine default_example(self, name)
58+
59+
!> Instance of the executable meta data
60+
type(example_config_t), intent(out) :: self
61+
62+
!> Name of the package
63+
character(len=*), intent(in) :: name
64+
65+
self%name = name
66+
self%source_dir = "example"
67+
self%main = "main.f90"
68+
69+
end subroutine default_example
70+
5471
!> Populate test in case we find the default test/ directory
5572
subroutine default_test(self, name)
5673

@@ -126,14 +143,24 @@ subroutine package_defaults(package, error)
126143
call default_executable(package%executable(1), package%name)
127144
end if
128145

146+
! Populate example in case we find the default example directory
147+
if (.not.allocated(package%example) .and. &
148+
exists(join_path("example","main.f90"))) then
149+
allocate(package%example(1))
150+
call default_example(package%example(1), package%name)
151+
endif
152+
129153
! Populate test in case we find the default test directory
130154
if (.not.allocated(package%test) .and. &
131155
exists(join_path("test","main.f90"))) then
132156
allocate(package%test(1))
133157
call default_test(package%test(1), package%name)
134158
endif
135159

136-
if (.not.(allocated(package%library) .or. allocated(package%executable))) then
160+
if (.not.(allocated(package%library) &
161+
& .or. allocated(package%executable) &
162+
& .or. allocated(package%example) &
163+
& .or. allocated(package%test))) then
137164
call fatal_error(error, "Neither library nor executable found, there is nothing to do")
138165
return
139166
end if

fpm/src/fpm/manifest/build.f90

Lines changed: 14 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@
55
!>```toml
66
!>[build]
77
!>auto-executables = bool
8+
!>auto-examples = bool
89
!>auto-tests = bool
910
!>link = ["lib"]
1011
!>```
@@ -24,6 +25,9 @@ module fpm_manifest_build
2425
!> Automatic discovery of executables
2526
logical :: auto_executables
2627

28+
!> Automatic discovery of examples
29+
logical :: auto_examples
30+
2731
!> Automatic discovery of tests
2832
logical :: auto_tests
2933

@@ -72,6 +76,14 @@ subroutine new_build_config(self, table, error)
7276
return
7377
end if
7478

79+
call get_value(table, "auto-examples", self%auto_examples, .true., stat=stat)
80+
81+
if (stat /= toml_stat%success) then
82+
call fatal_error(error,"Error while reading value for 'auto-examples' in fpm.toml, expecting logical")
83+
return
84+
end if
85+
86+
7587
call get_value(table, "link", self%link, error)
7688
if (allocated(error)) return
7789

@@ -98,7 +110,7 @@ subroutine check(table, error)
98110
do ikey = 1, size(list)
99111
select case(list(ikey)%key)
100112

101-
case("auto-executables", "auto-tests", "link")
113+
case("auto-executables", "auto-examples", "auto-tests", "link")
102114
continue
103115

104116
case default
@@ -136,6 +148,7 @@ subroutine info(self, unit, verbosity)
136148

137149
write(unit, fmt) "Build configuration"
138150
write(unit, fmt) " - auto-discovery (apps) ", merge("enabled ", "disabled", self%auto_executables)
151+
write(unit, fmt) " - auto-discovery (examples) ", merge("enabled ", "disabled", self%auto_examples)
139152
write(unit, fmt) " - auto-discovery (tests) ", merge("enabled ", "disabled", self%auto_tests)
140153
if (allocated(self%link)) then
141154
write(unit, fmt) " - link against"

0 commit comments

Comments
 (0)