Skip to content

Commit 93780ca

Browse files
authored
Merge branch 'main' into differentiate-flangs
2 parents 7d2509f + e01591b commit 93780ca

33 files changed

+5316
-1315
lines changed

ci/run_tests.sh

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -164,6 +164,11 @@ pushd program_with_module
164164
"$fpm" run --target Program_with_module
165165
popd
166166

167+
pushd program_with_cpp_guarded_module
168+
"$fpm" build
169+
"$fpm" run
170+
popd
171+
167172
pushd link_executable
168173
"$fpm" build
169174
"$fpm" run --target gomp_test
@@ -366,5 +371,8 @@ pushd both_lib_types
366371
test $(ls lib/libboth_lib_types* | wc -l) -eq 2
367372
popd
368373

374+
# Test custom build directory functionality
375+
bash "../ci/test_custom_build_dir.sh" "$fpm" hello_world
376+
369377
# Cleanup
370378
rm -rf ./*/build

ci/test_custom_build_dir.sh

Lines changed: 98 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,98 @@
1+
#!/usr/bin/env bash
2+
set -ex
3+
4+
# Test script for custom build directory functionality
5+
# Usage: ./test_custom_build_dir.sh [fpm_executable] [example_package_dir]
6+
7+
if [ "$1" ]; then
8+
fpm="$1"
9+
else
10+
fpm=fpm
11+
fi
12+
13+
if [ "$2" ]; then
14+
test_package="$2"
15+
else
16+
test_package="hello_world"
17+
fi
18+
19+
echo "Testing custom build directory functionality with package: $test_package"
20+
21+
# Test 1: Custom build directory with CLI option
22+
pushd "$test_package"
23+
echo "Test 1: CLI option --build-dir"
24+
rm -rf ./build custom_build_test
25+
"$fpm" build --build-dir custom_build_test
26+
test -d custom_build_test
27+
test -f custom_build_test/.gitignore
28+
"$fpm" run --build-dir custom_build_test --target "$test_package"
29+
# Verify standard build directory was not created
30+
test ! -d build
31+
echo "✓ CLI option --build-dir works"
32+
33+
# Test 2: Environment variable
34+
echo "Test 2: Environment variable FPM_BUILD_DIR"
35+
rm -rf custom_build_test env_build_test
36+
FPM_BUILD_DIR=env_build_test "$fpm" build
37+
test -d env_build_test
38+
test -f env_build_test/.gitignore
39+
FPM_BUILD_DIR=env_build_test "$fpm" run --target "$test_package"
40+
echo "✓ Environment variable FPM_BUILD_DIR works"
41+
42+
# Test 3: CLI option overrides environment variable
43+
echo "Test 3: CLI option overrides environment variable"
44+
rm -rf env_build_test cli_override_test
45+
FPM_BUILD_DIR=env_build_test "$fpm" build --build-dir cli_override_test
46+
test -d cli_override_test
47+
test ! -d env_build_test
48+
echo "✓ CLI option correctly overrides environment variable"
49+
50+
# Test 4: Build directory validation - reserved names
51+
echo "Test 4: Build directory validation"
52+
# These should fail with specific error messages
53+
if "$fpm" build --build-dir src 2>&1 | grep -q "conflicts with source directory"; then
54+
echo "✓ Correctly rejected 'src'"
55+
else
56+
echo "ERROR: Should reject 'src'" && exit 1
57+
fi
58+
59+
if "$fpm" build --build-dir app 2>&1 | grep -q "conflicts with source directory"; then
60+
echo "✓ Correctly rejected 'app'"
61+
else
62+
echo "ERROR: Should reject 'app'" && exit 1
63+
fi
64+
65+
if "$fpm" build --build-dir test 2>&1 | grep -q "conflicts with source directory"; then
66+
echo "✓ Correctly rejected 'test'"
67+
else
68+
echo "ERROR: Should reject 'test'" && exit 1
69+
fi
70+
71+
if "$fpm" build --build-dir . 2>&1 | grep -q "would overwrite the current"; then
72+
echo "✓ Correctly rejected '.'"
73+
else
74+
echo "ERROR: Should reject '.'" && exit 1
75+
fi
76+
77+
# Test 5: Path normalization
78+
echo "Test 5: Path normalization"
79+
if "$fpm" build --build-dir ./src 2>&1 | grep -q "conflicts with source directory"; then
80+
echo "✓ Correctly rejected './src' (path normalization works)"
81+
else
82+
echo "ERROR: Should reject './src'" && exit 1
83+
fi
84+
85+
# Test 6: Different commands with custom build directory
86+
echo "Test 6: Different commands with custom build directory"
87+
rm -rf test_build_all
88+
"$fpm" build --build-dir test_build_all
89+
"$fpm" run --build-dir test_build_all --target "$test_package"
90+
# Some packages may not have tests, so this might fail but that's expected
91+
"$fpm" test --build-dir test_build_all 2>/dev/null || echo "No tests in $test_package (expected)"
92+
echo "✓ All commands work with custom build directory"
93+
94+
# Cleanup test directories
95+
rm -rf custom_build_test env_build_test cli_override_test test_build_all
96+
popd
97+
98+
echo "All custom build directory tests passed!"
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
build/*
Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,12 @@
1+
program program_with_module
2+
#if defined(HAVE_MODULE)
3+
use greet_m, only: greeting
4+
#endif
5+
implicit none
6+
7+
#ifndef HAVE_MODULE
8+
print *, 'OK without module'
9+
#else
10+
print *, greeting
11+
#endif
12+
end program program_with_module
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
name = "Program_with_cpp_guarded_module"
2+
# Enable CPP but do not define macros
3+
[preprocess.cpp]

src/fpm.f90

Lines changed: 82 additions & 48 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@ module fpm
1919
use fpm_targets, only: targets_from_sources, build_target_t, build_target_ptr, &
2020
FPM_TARGET_EXECUTABLE, get_library_dirs, filter_executable_targets
2121
use fpm_manifest, only : get_package_data, package_config_t
22+
use fpm_manifest_platform, only: platform_config_t
2223
use fpm_meta, only : resolve_metapackages
2324
use fpm_error, only : error_t, fatal_error, fpm_stop
2425
use fpm_toml, only: name_is_json
@@ -37,26 +38,30 @@ module fpm
3738
contains
3839

3940
!> Constructs a valid fpm model from command line settings and the toml manifest.
40-
subroutine build_model(model, settings, package, error)
41+
subroutine build_model(model, settings, package_config, error)
4142
type(fpm_model_t), intent(out) :: model
4243
class(fpm_build_settings), intent(inout) :: settings
43-
type(package_config_t), intent(inout), target :: package
44+
type(package_config_t), intent(inout), target :: package_config
4445
type(error_t), allocatable, intent(out) :: error
4546

4647
integer :: i, j
47-
type(package_config_t), target :: dependency
48+
type(package_config_t), target :: package, dependency_config, dependency
4849
type(package_config_t), pointer :: manifest
50+
type(platform_config_t) :: target_platform
4951
character(len=:), allocatable :: file_name, lib_dir
5052
logical :: has_cpp
51-
logical :: duplicates_found
53+
logical :: duplicates_found, auto_exe, auto_example, auto_test
5254
type(string_t) :: include_dir
5355

54-
model%package_name = package%name
56+
model%package_name = package_config%name
57+
58+
! Set target OS to current OS (may be extended for cross-compilation in the future)
59+
model%target_os = get_os_type()
5560

5661
allocate(model%include_dirs(0))
5762
allocate(model%link_libraries(0))
5863
allocate(model%external_modules(0))
59-
64+
6065
call new_compiler(model%compiler, settings%compiler, settings%c_compiler, &
6166
& settings%cxx_compiler, echo=settings%verbose, verbose=settings%verbose)
6267
call new_archiver(model%archiver, settings%archiver, &
@@ -67,20 +72,30 @@ subroutine build_model(model, settings, package, error)
6772
"<WARN>", "Unknown compiler", model%compiler%fc, "requested!", &
6873
"Defaults for this compiler might be incorrect"
6974
end if
70-
75+
76+
! Extract the target platform for this build
77+
target_platform = model%target_platform()
78+
7179
call new_compiler_flags(model,settings)
72-
model%build_prefix = join_path("build", basename(model%compiler%fc))
73-
model%include_tests = settings%build_tests
74-
model%enforce_module_names = package%build%module_naming
75-
model%module_prefix = package%build%module_prefix
76-
80+
model%build_dir = settings%build_dir
81+
model%build_prefix = join_path(settings%build_dir, basename(model%compiler%fc))
82+
model%include_tests = settings%build_tests
83+
84+
! Extract the current package configuration request
85+
package = package_config%export_config(target_platform)
86+
7787
! Resolve meta-dependencies into the package and the model
7888
call resolve_metapackages(model,package,settings,error)
7989
if (allocated(error)) return
8090

91+
if (allocated(package%build)) then
92+
model%enforce_module_names = package%build%module_naming
93+
model%module_prefix = package%build%module_prefix
94+
endif
95+
8196
! Create dependencies
82-
call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml"), &
83-
& path_to_config=settings%path_to_config)
97+
call new_dependency_tree(model%deps, cache=join_path(settings%build_dir, "cache.toml"), &
98+
& path_to_config=settings%path_to_config, build_dir=settings%build_dir)
8499

85100
! Build and resolve model dependencies
86101
call model%deps%add(package, error)
@@ -90,9 +105,9 @@ subroutine build_model(model, settings, package, error)
90105
call model%deps%update(error)
91106
if (allocated(error)) return
92107

93-
! build/ directory should now exist
94-
if (.not.exists("build/.gitignore")) then
95-
call filewrite(join_path("build", ".gitignore"),["*"])
108+
! build directory should now exist
109+
if (.not.exists(join_path(settings%build_dir, ".gitignore"))) then
110+
call filewrite(join_path(settings%build_dir, ".gitignore"),["*"])
96111
end if
97112

98113
allocate(model%packages(model%deps%ndep))
@@ -108,19 +123,20 @@ subroutine build_model(model, settings, package, error)
108123
manifest => package
109124
else
110125

111-
call get_package_data(dependency, file_name, error, apply_defaults=.true.)
112-
if (allocated(error)) exit
126+
! Extract this dependency config
127+
call get_package_data(dependency_config, file_name, error, apply_defaults=.true.)
128+
if (allocated(error)) exit
129+
130+
! Adapt it to the current profile/platform
131+
dependency = dependency_config%export_config(target_platform)
113132

114133
manifest => dependency
115134
end if
116135

117-
model%packages(i)%name = manifest%name
118-
associate(features => model%packages(i)%features)
119-
features%implicit_typing = manifest%fortran%implicit_typing
120-
features%implicit_external = manifest%fortran%implicit_external
121-
features%source_form = manifest%fortran%source_form
122-
end associate
123-
model%packages(i)%version = manifest%version
136+
137+
model%packages(i)%name = manifest%name
138+
model%packages(i)%features = manifest%fortran
139+
model%packages(i)%version = manifest%version
124140

125141
!> Add this dependency's manifest macros
126142
if (allocated(manifest%preprocess)) then
@@ -146,7 +162,8 @@ subroutine build_model(model, settings, package, error)
146162
lib_dir = join_path(dep%proj_dir, manifest%library%source_dir)
147163
if (is_dir(lib_dir)) then
148164
call add_sources_from_dir(model%packages(i)%sources, lib_dir, FPM_SCOPE_LIB, &
149-
with_f_ext=model%packages(i)%preprocess%suffixes, error=error)
165+
with_f_ext=model%packages(i)%preprocess%suffixes, error=error, &
166+
preprocess=model%packages(i)%preprocess)
150167
if (allocated(error)) exit
151168
end if
152169
end if
@@ -161,18 +178,22 @@ subroutine build_model(model, settings, package, error)
161178
end if
162179

163180
end if
181+
182+
if (allocated(manifest%build)) then
164183

165-
if (allocated(manifest%build%link)) then
166-
model%link_libraries = [model%link_libraries, manifest%build%link]
167-
end if
184+
if (allocated(manifest%build%link)) then
185+
model%link_libraries = [model%link_libraries, manifest%build%link]
186+
end if
168187

169-
if (allocated(manifest%build%external_modules)) then
170-
model%external_modules = [model%external_modules, manifest%build%external_modules]
171-
end if
188+
if (allocated(manifest%build%external_modules)) then
189+
model%external_modules = [model%external_modules, manifest%build%external_modules]
190+
end if
172191

173-
! Copy naming conventions from this dependency's manifest
174-
model%packages(i)%enforce_module_names = manifest%build%module_naming
175-
model%packages(i)%module_prefix = manifest%build%module_prefix
192+
! Copy naming conventions from this dependency's manifest
193+
model%packages(i)%enforce_module_names = manifest%build%module_naming
194+
model%packages(i)%module_prefix = manifest%build%module_prefix
195+
196+
endif
176197

177198
end associate
178199
end do
@@ -182,30 +203,43 @@ subroutine build_model(model, settings, package, error)
182203
if (has_cpp) call set_cpp_preprocessor_flags(model%compiler%id, model%fortran_compile_flags)
183204

184205
! Add sources from executable directories
185-
if (is_dir('app') .and. package%build%auto_executables) then
206+
207+
if (allocated(package%build)) then
208+
auto_exe = package%build%auto_executables
209+
auto_example = package%build%auto_examples
210+
auto_test = package%build%auto_tests
211+
else
212+
auto_exe = .true.
213+
auto_example = .true.
214+
auto_test = .true.
215+
endif
216+
217+
if (is_dir('app') .and. auto_exe) then
186218
call add_sources_from_dir(model%packages(1)%sources,'app', FPM_SCOPE_APP, &
187219
with_executables=.true., with_f_ext=model%packages(1)%preprocess%suffixes,&
188-
error=error)
220+
error=error,preprocess=model%packages(1)%preprocess)
189221

190222
if (allocated(error)) then
191223
return
192224
end if
193225

194226
end if
195-
if (is_dir('example') .and. package%build%auto_examples) then
227+
if (is_dir('example') .and. auto_example) then
196228
call add_sources_from_dir(model%packages(1)%sources,'example', FPM_SCOPE_EXAMPLE, &
197229
with_executables=.true., &
198-
with_f_ext=model%packages(1)%preprocess%suffixes,error=error)
230+
with_f_ext=model%packages(1)%preprocess%suffixes,error=error,&
231+
preprocess=model%packages(1)%preprocess)
199232

200233
if (allocated(error)) then
201234
return
202235
end if
203236

204237
end if
205-
if (is_dir('test') .and. package%build%auto_tests) then
238+
if (is_dir('test') .and. auto_test) then
206239
call add_sources_from_dir(model%packages(1)%sources,'test', FPM_SCOPE_TEST, &
207240
with_executables=.true., &
208-
with_f_ext=model%packages(1)%preprocess%suffixes,error=error)
241+
with_f_ext=model%packages(1)%preprocess%suffixes,error=error,&
242+
preprocess=model%packages(1)%preprocess)
209243

210244
if (allocated(error)) then
211245
return
@@ -214,9 +248,9 @@ subroutine build_model(model, settings, package, error)
214248
end if
215249
if (allocated(package%executable)) then
216250
call add_executable_sources(model%packages(1)%sources, package%executable, FPM_SCOPE_APP, &
217-
auto_discover=package%build%auto_executables, &
251+
auto_discover=auto_exe, &
218252
with_f_ext=model%packages(1)%preprocess%suffixes, &
219-
error=error)
253+
error=error,preprocess=model%packages(1)%preprocess)
220254

221255
if (allocated(error)) then
222256
return
@@ -225,9 +259,9 @@ subroutine build_model(model, settings, package, error)
225259
end if
226260
if (allocated(package%example)) then
227261
call add_executable_sources(model%packages(1)%sources, package%example, FPM_SCOPE_EXAMPLE, &
228-
auto_discover=package%build%auto_examples, &
262+
auto_discover=auto_example, &
229263
with_f_ext=model%packages(1)%preprocess%suffixes, &
230-
error=error)
264+
error=error,preprocess=model%packages(1)%preprocess)
231265

232266
if (allocated(error)) then
233267
return
@@ -236,9 +270,9 @@ subroutine build_model(model, settings, package, error)
236270
end if
237271
if (allocated(package%test)) then
238272
call add_executable_sources(model%packages(1)%sources, package%test, FPM_SCOPE_TEST, &
239-
auto_discover=package%build%auto_tests, &
273+
auto_discover=auto_test, &
240274
with_f_ext=model%packages(1)%preprocess%suffixes, &
241-
error=error)
275+
error=error,preprocess=model%packages(1)%preprocess)
242276

243277
if (allocated(error)) then
244278
return

0 commit comments

Comments
 (0)