Skip to content
3 changes: 3 additions & 0 deletions ci/run_tests.sh
Original file line number Diff line number Diff line change
Expand Up @@ -366,5 +366,8 @@ pushd both_lib_types
test $(ls lib/libboth_lib_types* | wc -l) -eq 2
popd

# Test custom build directory functionality
bash "../ci/test_custom_build_dir.sh" "$fpm" hello_world

# Cleanup
rm -rf ./*/build
98 changes: 98 additions & 0 deletions ci/test_custom_build_dir.sh
Original file line number Diff line number Diff line change
@@ -0,0 +1,98 @@
#!/usr/bin/env bash
set -ex

# Test script for custom build directory functionality
# Usage: ./test_custom_build_dir.sh [fpm_executable] [example_package_dir]

if [ "$1" ]; then
fpm="$1"
else
fpm=fpm
fi

if [ "$2" ]; then
test_package="$2"
else
test_package="hello_world"
fi

echo "Testing custom build directory functionality with package: $test_package"

# Test 1: Custom build directory with CLI option
pushd "$test_package"
echo "Test 1: CLI option --build-dir"
rm -rf ./build custom_build_test
"$fpm" build --build-dir custom_build_test
test -d custom_build_test
test -f custom_build_test/.gitignore
"$fpm" run --build-dir custom_build_test --target "$test_package"
# Verify standard build directory was not created
test ! -d build
echo "✓ CLI option --build-dir works"

# Test 2: Environment variable
echo "Test 2: Environment variable FPM_BUILD_DIR"
rm -rf custom_build_test env_build_test
FPM_BUILD_DIR=env_build_test "$fpm" build
test -d env_build_test
test -f env_build_test/.gitignore
FPM_BUILD_DIR=env_build_test "$fpm" run --target "$test_package"
echo "✓ Environment variable FPM_BUILD_DIR works"

# Test 3: CLI option overrides environment variable
echo "Test 3: CLI option overrides environment variable"
rm -rf env_build_test cli_override_test
FPM_BUILD_DIR=env_build_test "$fpm" build --build-dir cli_override_test
test -d cli_override_test
test ! -d env_build_test
echo "✓ CLI option correctly overrides environment variable"

# Test 4: Build directory validation - reserved names
echo "Test 4: Build directory validation"
# These should fail with specific error messages
if "$fpm" build --build-dir src 2>&1 | grep -q "conflicts with source directory"; then
echo "✓ Correctly rejected 'src'"
else
echo "ERROR: Should reject 'src'" && exit 1
fi

if "$fpm" build --build-dir app 2>&1 | grep -q "conflicts with source directory"; then
echo "✓ Correctly rejected 'app'"
else
echo "ERROR: Should reject 'app'" && exit 1
fi

if "$fpm" build --build-dir test 2>&1 | grep -q "conflicts with source directory"; then
echo "✓ Correctly rejected 'test'"
else
echo "ERROR: Should reject 'test'" && exit 1
fi

if "$fpm" build --build-dir . 2>&1 | grep -q "would overwrite the current"; then
echo "✓ Correctly rejected '.'"
else
echo "ERROR: Should reject '.'" && exit 1
fi

# Test 5: Path normalization
echo "Test 5: Path normalization"
if "$fpm" build --build-dir ./src 2>&1 | grep -q "conflicts with source directory"; then
echo "✓ Correctly rejected './src' (path normalization works)"
else
echo "ERROR: Should reject './src'" && exit 1
fi

# Test 6: Different commands with custom build directory
echo "Test 6: Different commands with custom build directory"
rm -rf test_build_all
"$fpm" build --build-dir test_build_all
"$fpm" run --build-dir test_build_all --target "$test_package"
# Some packages may not have tests, so this might fail but that's expected
"$fpm" test --build-dir test_build_all 2>/dev/null || echo "No tests in $test_package (expected)"
echo "✓ All commands work with custom build directory"

# Cleanup test directories
rm -rf custom_build_test env_build_test cli_override_test test_build_all
popd

echo "All custom build directory tests passed!"
13 changes: 7 additions & 6 deletions src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,8 @@ subroutine build_model(model, settings, package, error)
end if

call new_compiler_flags(model,settings)
model%build_prefix = join_path("build", basename(model%compiler%fc))
model%build_dir = settings%build_dir
model%build_prefix = join_path(settings%build_dir, basename(model%compiler%fc))
model%include_tests = settings%build_tests
model%enforce_module_names = package%build%module_naming
model%module_prefix = package%build%module_prefix
Expand All @@ -79,8 +80,8 @@ subroutine build_model(model, settings, package, error)
if (allocated(error)) return

! Create dependencies
call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml"), &
& path_to_config=settings%path_to_config)
call new_dependency_tree(model%deps, cache=join_path(settings%build_dir, "cache.toml"), &
& path_to_config=settings%path_to_config, build_dir=settings%build_dir)

! Build and resolve model dependencies
call model%deps%add(package, error)
Expand All @@ -90,9 +91,9 @@ subroutine build_model(model, settings, package, error)
call model%deps%update(error)
if (allocated(error)) return

! build/ directory should now exist
if (.not.exists("build/.gitignore")) then
call filewrite(join_path("build", ".gitignore"),["*"])
! build directory should now exist
if (.not.exists(join_path(settings%build_dir, ".gitignore"))) then
call filewrite(join_path(settings%build_dir, ".gitignore"),["*"])
end if

allocate(model%packages(model%deps%ndep))
Expand Down
4 changes: 2 additions & 2 deletions src/fpm/cmd/export.f90
Original file line number Diff line number Diff line change
Expand Up @@ -44,8 +44,8 @@ subroutine cmd_export(settings)
if (len_trim(settings%dump_dependencies)>0) then

!> Generate dependency tree
filename = join_path("build", "cache.toml")
call new_dependency_tree(deps, cache=filename, verbosity=merge(2, 1, settings%verbose))
filename = join_path(settings%build_dir, "cache.toml")
call new_dependency_tree(deps, cache=filename, verbosity=merge(2, 1, settings%verbose), build_dir=settings%build_dir)
call deps%add(package, error)
call handle_error(error)

Expand Down
17 changes: 10 additions & 7 deletions src/fpm/cmd/update.f90
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
module fpm_cmd_update
use fpm_command_line, only : fpm_update_settings
use fpm_command_line, only : fpm_update_settings, get_fpm_env
use fpm_dependency, only : dependency_tree_t, new_dependency_tree
use fpm_error, only : error_t, fpm_stop
use fpm_filesystem, only : exists, mkdir, join_path, delete_file, filewrite
Expand All @@ -20,21 +20,24 @@ subroutine cmd_update(settings)
type(dependency_tree_t) :: deps
type(error_t), allocatable :: error
integer :: ii
character(len=:), allocatable :: cache
character(len=:), allocatable :: cache, build_dir

call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
call handle_error(error)

if (.not. exists("build")) then
call mkdir("build")
call filewrite(join_path("build", ".gitignore"),["*"])
! Get build directory from environment variable or use default
build_dir = get_fpm_env("BUILD_DIR", "build")

if (.not. exists(build_dir)) then
call mkdir(build_dir)
call filewrite(join_path(build_dir, ".gitignore"),["*"])
end if

cache = join_path("build", "cache.toml")
cache = join_path(build_dir, "cache.toml")
if (settings%clean) call delete_file(cache)

call new_dependency_tree(deps, cache=cache, verbosity=merge(2, 1, settings%verbose), &
& path_to_config=settings%path_to_config)
& path_to_config=settings%path_to_config, build_dir=build_dir)

call deps%add(package, error)
call handle_error(error)
Expand Down
10 changes: 8 additions & 2 deletions src/fpm/dependency.f90
Original file line number Diff line number Diff line change
Expand Up @@ -205,7 +205,7 @@ module fpm_dependency
contains

!> Create a new dependency tree
subroutine new_dependency_tree(self, verbosity, cache, path_to_config)
subroutine new_dependency_tree(self, verbosity, cache, path_to_config, build_dir)
!> Instance of the dependency tree
type(dependency_tree_t), intent(out) :: self
!> Verbosity of printout
Expand All @@ -214,9 +214,15 @@ subroutine new_dependency_tree(self, verbosity, cache, path_to_config)
character(len=*), intent(in), optional :: cache
!> Path to the global config file.
character(len=*), intent(in), optional :: path_to_config
!> Custom build directory
character(len=*), intent(in), optional :: build_dir

call resize(self%dep)
self%dep_dir = join_path("build", "dependencies")
if (present(build_dir)) then
self%dep_dir = join_path(build_dir, "dependencies")
else
self%dep_dir = join_path("build", "dependencies")
end if

if (present(verbosity)) self%verbosity = verbosity

Expand Down
2 changes: 1 addition & 1 deletion src/fpm_backend.F90
Original file line number Diff line number Diff line change
Expand Up @@ -115,7 +115,7 @@ subroutine build_package(targets,model,verbose,dry_run)
plain_output = .true.
#endif

progress = build_progress_t(queue,plain_output)
progress = build_progress_t(queue,plain_output,model%build_dir)

! Loop over parallel schedule regions
do i=1,size(schedule_ptr)-1
Expand Down
14 changes: 12 additions & 2 deletions src/fpm_backend_output.f90
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,8 @@ module fpm_backend_output
logical :: plain_mode = .true.
!> Store needed when updating previous console lines
integer, allocatable :: output_lines(:)
!> Build directory
character(:), allocatable :: build_dir
!> Queue of scheduled build targets
type(build_target_ptr), pointer :: target_queue(:)
!> The compile_commands.json table
Expand All @@ -56,11 +58,13 @@ module fpm_backend_output
contains

!> Initialise a new build progress object
function new_build_progress(target_queue,plain_mode) result(progress)
function new_build_progress(target_queue,plain_mode,build_dir) result(progress)
!> The queue of scheduled targets
type(build_target_ptr), intent(in), target :: target_queue(:)
!> Enable 'plain' output for progress object
logical, intent(in), optional :: plain_mode
!> Build directory
character(*), intent(in), optional :: build_dir
!> Progress object to initialise
type(build_progress_t) :: progress

Expand All @@ -71,6 +75,12 @@ function new_build_progress(target_queue,plain_mode) result(progress)
progress%plain_mode = plain_mode
progress%n_complete = 0

if (present(build_dir)) then
progress%build_dir = build_dir
else
progress%build_dir = "build"
end if

allocate(progress%output_lines(progress%n_target))

end function new_build_progress
Expand Down Expand Up @@ -191,7 +201,7 @@ subroutine output_write_compile_commands(progress,error)
type(error_t), allocatable :: error

! Write compile commands
path = join_path('build','compile_commands.json')
path = join_path(progress%build_dir,'compile_commands.json')

call progress%compile_commands%write(filename=path, error=error)

Expand Down
Loading
Loading