diff options
-rwxr-xr-x | ci/run_tests.bat | 25 | ||||
-rwxr-xr-x | ci/run_tests.sh | 10 | ||||
-rw-r--r-- | fpm/src/fpm.f90 | 141 | ||||
-rw-r--r-- | fpm/src/fpm/git.f90 | 43 | ||||
-rw-r--r-- | fpm/src/fpm_backend.f90 | 13 | ||||
-rw-r--r-- | test/example_packages/README.md | 6 |
6 files changed, 216 insertions, 22 deletions
diff --git a/ci/run_tests.bat b/ci/run_tests.bat index 76e5349..645fd49 100755 --- a/ci/run_tests.bat +++ b/ci/run_tests.bat @@ -15,6 +15,7 @@ if errorlevel 1 exit 1 build\gfortran_debug\app\fpm if errorlevel 1 exit 1 + cd ..\test\example_packages\hello_world if errorlevel 1 exit 1 @@ -25,6 +26,30 @@ if errorlevel 1 exit 1 if errorlevel 1 exit 1 +cd ..\hello_fpm +if errorlevel 1 exit 1 + +..\..\..\fpm\build\gfortran_debug\app\fpm build +if errorlevel 1 exit 1 + +.\build\gfortran_debug\app\hello_fpm +if errorlevel 1 exit 1 + + +cd ..\circular_test +if errorlevel 1 exit 1 + +..\..\..\fpm\build\gfortran_debug\app\fpm build +if errorlevel 1 exit 1 + + +cd ..\circular_example +if errorlevel 1 exit 1 + +..\..\..\fpm\build\gfortran_debug\app\fpm build +if errorlevel 1 exit 1 + + cd ..\hello_complex if errorlevel 1 exit 1 diff --git a/ci/run_tests.sh b/ci/run_tests.sh index adff2b3..7ca33d8 100755 --- a/ci/run_tests.sh +++ b/ci/run_tests.sh @@ -12,6 +12,16 @@ cd ../test/example_packages/hello_world ../../../fpm/build/gfortran_debug/app/fpm build ./build/gfortran_debug/app/hello_world +cd ../hello_fpm +../../../fpm/build/gfortran_debug/app/fpm build +./build/gfortran_debug/app/hello_fpm + +cd ../circular_test +../../../fpm/build/gfortran_debug/app/fpm build + +cd ../circular_example +../../../fpm/build/gfortran_debug/app/fpm build + cd ../hello_complex ../../../fpm/build/gfortran_debug/app/fpm build ./build/gfortran_debug/app/say_Hello diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index bd93b2a..55b2baa 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -1,6 +1,5 @@ module fpm - -use fpm_strings, only: string_t, str_ends_with +use fpm_strings, only: string_t, str_ends_with, operator(.in.) use fpm_backend, only: build_package use fpm_command_line, only: fpm_build_settings, fpm_new_settings, & fpm_run_settings, fpm_install_settings, fpm_test_settings @@ -14,10 +13,11 @@ use fpm_sources, only: add_executable_sources, add_sources_from_dir, & resolve_module_dependencies use fpm_manifest, only : get_package_data, default_executable, & default_library, package_t -use fpm_error, only : error_t +use fpm_error, only : error_t, fatal_error use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, & & stdout=>output_unit, & & stderr=>error_unit +use fpm_manifest_dependency, only: dependency_t implicit none private public :: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test @@ -25,6 +25,123 @@ public :: cmd_build, cmd_install, cmd_new, cmd_run, cmd_test contains + +recursive subroutine add_libsources_from_package(sources,package_list,package, & + package_root,dev_depends,error) + ! Discover library sources in a package, recursively including dependencies + ! Only supports local path dependencies currently + ! + type(srcfile_t), allocatable, intent(inout), target :: sources(:) + type(string_t), allocatable, intent(inout) :: package_list(:) + type(package_t), intent(in) :: package + character(*), intent(in) :: package_root + logical, intent(in) :: dev_depends + type(error_t), allocatable, intent(out) :: error + + ! Add package library sources + if (allocated(package%library)) then + + call add_sources_from_dir(sources, join_path(package_root,package%library%source_dir), & + FPM_SCOPE_LIB, error=error) + + if (allocated(error)) then + return + end if + + end if + + ! Add library sources from dependencies + if (allocated(package%dependency)) then + + call add_dependencies(package%dependency) + + if (allocated(error)) then + return + end if + + end if + + ! Add library sources from dev-dependencies + if (dev_depends .and. allocated(package%dev_dependency)) then + + call add_dependencies(package%dev_dependency) + + if (allocated(error)) then + return + end if + + end if + + contains + + subroutine add_dependencies(dependency_list) + type(dependency_t) :: dependency_list(:) + + integer :: i + type(string_t) :: dep_name + type(package_t) :: dependency + + character(:), allocatable :: dependency_path + + do i=1,size(dependency_list) + + if (dependency_list(i)%name .in. package_list) then + cycle + end if + + if (allocated(dependency_list(i)%git)) then + + dependency_path = join_path('build','dependencies',dependency_list(i)%name) + + if (.not.exists(join_path(dependency_path,'fpm.toml'))) then + call dependency_list(i)%git%checkout(dependency_path, error) + if (allocated(error)) return + end if + + else if (allocated(dependency_list(i)%path)) then + + dependency_path = join_path(package_root,dependency_list(i)%path) + + end if + + call get_package_data(dependency, & + join_path(dependency_path,"fpm.toml"), error) + + if (allocated(error)) then + error%message = 'Error while parsing manifest for dependency package at:'//& + new_line('a')//join_path(dependency_path,"fpm.toml")//& + new_line('a')//error%message + return + end if + + if (.not.allocated(dependency%library) .and. & + exists(join_path(dependency_path,"src"))) then + allocate(dependency%library) + dependency%library%source_dir = "src" + end if + + + call add_libsources_from_package(sources,package_list,dependency, & + package_root=dependency_path, & + dev_depends=dev_depends, error=error) + + if (allocated(error)) then + error%message = 'Error while processing sources for dependency package "'//& + new_line('a')//dependency%name//'"'//& + new_line('a')//error%message + return + end if + + dep_name%s = dependency_list(i)%name + package_list = [package_list, dep_name] + + end do + + end subroutine add_dependencies + +end subroutine add_libsources_from_package + + subroutine build_model(model, settings, package, error) ! Constructs a valid fpm model from command line settings and toml manifest ! @@ -33,8 +150,13 @@ subroutine build_model(model, settings, package, error) type(package_t), intent(in) :: package type(error_t), allocatable, intent(out) :: error + type(string_t), allocatable :: package_list(:) + model%package_name = package%name + allocate(package_list(1)) + package_list(1)%s = package%name + ! #TODO: Choose flags and output directory based on cli settings & manifest inputs model%fortran_compiler = 'gfortran' @@ -96,14 +218,11 @@ subroutine build_model(model, settings, package, error) end if - if (allocated(package%library)) then - call add_sources_from_dir(model%sources, package%library%source_dir, & - FPM_SCOPE_LIB, error=error) - - if (allocated(error)) then - return - end if - + ! Add library sources, including local dependencies + call add_libsources_from_package(model%sources,package_list,package, & + package_root='.',dev_depends=.true.,error=error) + if (allocated(error)) then + return end if call resolve_module_dependencies(model%sources,error) diff --git a/fpm/src/fpm/git.f90 b/fpm/src/fpm/git.f90 index 28ae867..f02d06f 100644 --- a/fpm/src/fpm/git.f90 +++ b/fpm/src/fpm/git.f90 @@ -1,5 +1,6 @@ !> Implementation for interacting with git repositories. module fpm_git + use fpm_error, only: error_t, fatal_error implicit none public :: git_target_t @@ -43,6 +44,9 @@ module fpm_git contains + !> Fetch and checkout in local directory + procedure :: checkout + !> Show information on instance procedure :: info @@ -124,6 +128,45 @@ contains end function git_target_tag + subroutine checkout(self,local_path, error) + + !> Instance of the git target + class(git_target_t), intent(in) :: self + + !> Local path to checkout in + character(*), intent(in) :: local_path + + !> Error + type(error_t), allocatable, intent(out) :: error + + !> Stat for execute_command_line + integer :: stat + + call execute_command_line("git init "//local_path, exitstat=stat) + + if (stat /= 0) then + call fatal_error(error,'Error while initiating git repository for remote dependency') + return + end if + + call execute_command_line("git -C "//local_path//" fetch "//self%url//& + " "//self%object, exitstat=stat) + + if (stat /= 0) then + call fatal_error(error,'Error while fetching git repository for remote dependency') + return + end if + + call execute_command_line("git -C "//local_path//" checkout -qf FETCH_HEAD", exitstat=stat) + + if (stat /= 0) then + call fatal_error(error,'Error while checking out git repository for remote dependency') + return + end if + + end subroutine checkout + + !> Show information on git target subroutine info(self, unit, verbosity) diff --git a/fpm/src/fpm_backend.f90 b/fpm/src/fpm_backend.f90 index 40460d7..d7005bf 100644 --- a/fpm/src/fpm_backend.f90 +++ b/fpm/src/fpm_backend.f90 @@ -3,7 +3,7 @@ module fpm_backend ! Implements the native fpm build backend use fpm_environment, only: run, get_os_type, OS_WINDOWS -use fpm_filesystem, only: basename, join_path, exists, mkdir +use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir use fpm_model, only: fpm_model_t, srcfile_t, FPM_UNIT_MODULE, & FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, & FPM_UNIT_CSOURCE, FPM_UNIT_PROGRAM, & @@ -113,6 +113,10 @@ recursive subroutine build_source(model,source_file,linking) object_file = get_object_name(model,source_file%file_name) + if (.not.exists(dirname(object_file))) then + call mkdir(dirname(object_file)) + end if + call run("gfortran -c " // source_file%file_name // model%fortran_compile_flags & // " -o " // object_file) linking = linking // " " // object_file @@ -145,13 +149,6 @@ function get_object_name(model,source_file_name) result(object_file) ! Exclude first directory level from path object_file = source_file_name(index(source_file_name,filesep)+1:) - ! Convert remaining directory separators to underscores - i = index(object_file,filesep) - do while(i > 0) - object_file(i:i) = '_' - i = index(object_file,filesep) - end do - ! Construct full target path object_file = join_path(model%output_directory, model%package_name, & object_file//'.o') diff --git a/test/example_packages/README.md b/test/example_packages/README.md index 79fadb1..65f4109 100644 --- a/test/example_packages/README.md +++ b/test/example_packages/README.md @@ -7,11 +7,11 @@ the features demonstrated in each package and which versions of fpm are supporte | Name | Features | Bootstrap (Haskell) fpm | fpm | |---------------------|---------------------------------------------------------------|:-----------------------:|:---:| | auto_discovery_off | Default layout with auto-discovery disabled | N | Y | -| circular_example | Local path dependency; circular dependency | Y | N | -| circular_test | Local path dependency; circular dependency | Y | N | +| circular_example | Local path dependency; circular dependency | Y | Y | +| circular_test | Local path dependency; circular dependency | Y | Y | | hello_complex | Non-standard directory layout; multiple tests and executables | Y | Y | | hello_complex_2 | Auto-discovery of tests and executables with modules | N | Y | -| hello_fpm | App-only; local path dependency | Y | N | +| hello_fpm | App-only; local path dependency | Y | Y | | hello_world | App-only | Y | Y | | makefile_complex | External build command (makefile); local path dependency | Y | N | | program_with_module | App-only; module+program in single source file | Y | Y | |