diff options
author | Brad Richardson <everythingfunctional@protonmail.com> | 2021-03-29 09:37:56 -0500 |
---|---|---|
committer | GitHub <noreply@github.com> | 2021-03-29 09:37:56 -0500 |
commit | b988fe8374d7a6d109bb3942357a28f8698e3fe7 (patch) | |
tree | db40416bc437f257a1d4f9966cf3b28982632722 | |
parent | 0560c74770b7234b0f23d9feda4c697481ecbb5e (diff) | |
parent | f77e0728082d76bf4a8fbf7a248bc147b3b9e349 (diff) | |
download | fpm-b988fe8374d7a6d109bb3942357a28f8698e3fe7.tar.gz fpm-b988fe8374d7a6d109bb3942357a28f8698e3fe7.zip |
Merge pull request #409 from everythingfunctional/allow-programs-access-to-subdirectories
Give Programs Access to Code in Subdirectories
-rw-r--r-- | fpm/src/fpm_targets.f90 | 66 | ||||
-rw-r--r-- | fpm/test/fpm_test/test_module_dependencies.f90 | 94 |
2 files changed, 93 insertions, 67 deletions
diff --git a/fpm/src/fpm_targets.f90 b/fpm/src/fpm_targets.f90 index 6a67e98..02bb600 100644 --- a/fpm/src/fpm_targets.f90 +++ b/fpm/src/fpm_targets.f90 @@ -1,14 +1,14 @@ !># Build target handling !> !> This module handles the construction of the build target list -!> from the sources list (`[[targets_from_sources]]`), the +!> from the sources list (`[[targets_from_sources]]`), the !> resolution of module-dependencies between build targets !> (`[[resolve_module_dependencies]]`), and the enumeration of !> objects required for link targets (`[[resolve_target_linking]]`). !> !> A build target (`[[build_target_t]]`) is a file to be generated !> by the backend (compilation and linking). -!> +!> !> @note The current implementation is ignorant to the existence of !> module files (`.mod`,`.smod`). Dependencies arising from modules !> are based on the corresponding object files (`.o`) only. @@ -83,13 +83,13 @@ type build_target_t !> Link flags for this build target character(:), allocatable :: link_flags - + !> Compile flags for this build target character(:), allocatable :: compile_flags !> Flag set when first visited to check for circular dependencies logical :: touched = .false. - + !> Flag set if build target is sorted for building logical :: sorted = .false. @@ -120,10 +120,10 @@ subroutine targets_from_sources(targets,model,error) type(error_t), intent(out), allocatable :: error call build_target_list(targets,model) - + call resolve_module_dependencies(targets,error) if (allocated(error)) return - + call resolve_target_linking(targets,model) end subroutine targets_from_sources @@ -185,18 +185,18 @@ subroutine build_target_list(targets,model) model%package_name,'lib'//model%package_name//'.a')) do j=1,size(model%packages) - + associate(sources=>model%packages(j)%sources) do i=1,size(sources) - + select case (sources(i)%unit_type) case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE) call add_target(targets,source = sources(i), & type = FPM_TARGET_OBJECT,& output_file = get_object_name(sources(i))) - + if (with_lib .and. sources(i)%unit_scope == FPM_SCOPE_LIB) then ! Archive depends on object call add_dependency(targets(1)%ptr, targets(size(targets))%ptr) @@ -208,7 +208,7 @@ subroutine build_target_list(targets,model) output_file = get_object_name(sources(i)), & source = sources(i) & ) - + if (sources(i)%unit_scope == FPM_SCOPE_APP) then exe_dir = 'app' @@ -235,7 +235,7 @@ subroutine build_target_list(targets,model) ! Executable depends on library call add_dependency(targets(size(targets))%ptr, targets(1)%ptr) end if - + end select end do @@ -248,15 +248,15 @@ subroutine build_target_list(targets,model) function get_object_name(source) result(object_file) ! Generate object target path from source name and model params - ! + ! ! type(srcfile_t), intent(in) :: source character(:), allocatable :: object_file - + integer :: i character(1), parameter :: filesep = '/' character(:), allocatable :: dir - + object_file = canon_path(source%file_name) ! Convert any remaining directory separators to underscores @@ -267,7 +267,7 @@ subroutine build_target_list(targets,model) end do object_file = join_path(model%output_directory,model%package_name,object_file)//'.o' - + end function get_object_name end subroutine build_target_list @@ -307,7 +307,7 @@ subroutine add_target(targets,type,output_file,source,link_libraries) if (present(source)) new_target%source = source if (present(link_libraries)) new_target%link_libraries = link_libraries allocate(new_target%dependencies(0)) - + targets = [targets, build_target_ptr(new_target)] end subroutine add_target @@ -323,23 +323,23 @@ subroutine add_dependency(target, dependency) end subroutine add_dependency -!> Add dependencies to source-based targets (`FPM_TARGET_OBJECT`) +!> Add dependencies to source-based targets (`FPM_TARGET_OBJECT`) !> based on any modules used by the corresponding source file. !> !>### Source file scoping -!> -!> Source files are assigned a scope of either `FPM_SCOPE_LIB`, +!> +!> Source files are assigned a scope of either `FPM_SCOPE_LIB`, !> `FPM_SCOPE_APP` or `FPM_SCOPE_TEST`. The scope controls which !> modules may be used by the source file: -!> +!> !> - Library sources (`FPM_SCOPE_LIB`) may only use modules !> also with library scope. This includes library modules !> from dependencies. !> !> - Executable sources (`FPM_SCOPE_APP`,`FPM_SCOPE_TEST`) may use !> library modules (including dependencies) as well as any modules -!> corresponding to source files __in the same directory__ as the -!> executable source. +!> corresponding to source files in the same directory or a +!> subdirectory of the executable source file. !> !> @warning If a module used by a source file cannot be resolved to !> a source file in the package of the correct scope, then a __fatal error__ @@ -354,7 +354,7 @@ subroutine resolve_module_dependencies(targets,error) integer :: i, j do i=1,size(targets) - + if (.not.allocated(targets(i)%ptr%source)) cycle do j=1,size(targets(i)%ptr%source%modules_used) @@ -363,7 +363,7 @@ subroutine resolve_module_dependencies(targets,error) ! Dependency satisfied in same file, skip cycle end if - + if (any(targets(i)%ptr%source%unit_scope == & [FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST])) then dep%ptr => & @@ -386,7 +386,7 @@ subroutine resolve_module_dependencies(targets,error) end do - end do + end do end subroutine resolve_module_dependencies @@ -418,7 +418,7 @@ function find_module_dependency(targets,module_name,include_dir) result(target_p exit case default if (present(include_dir)) then - if (dirname(targets(k)%ptr%source%file_name) == include_dir) then + if (index(dirname(targets(k)%ptr%source%file_name), include_dir) == 1) then ! source file is within the include_dir or a subdirectory target_ptr => targets(k)%ptr exit end if @@ -427,7 +427,7 @@ function find_module_dependency(targets,module_name,include_dir) result(target_p end if end do - + end do end function find_module_dependency @@ -523,13 +523,13 @@ contains do i=1,size(target%dependencies) associate(dep => target%dependencies(i)%ptr) - + if (.not.allocated(dep%source)) cycle - + ! Skip library dependencies for executable targets - ! since the library archive will always be linked + ! since the library archive will always be linked if (is_exe.and.(dep%source%unit_scope == FPM_SCOPE_LIB)) cycle - + ! Skip if dependency object already listed if (dep%output_file .in. link_objects) cycle @@ -537,10 +537,10 @@ contains temp_str%s = dep%output_file link_objects = [link_objects, temp_str] - ! For executable objects, also need to include non-library + ! For executable objects, also need to include non-library ! dependencies from dependencies (recurse) if (is_exe) call get_link_objects(link_objects,dep,is_exe=.true.) - + end associate end do diff --git a/fpm/test/fpm_test/test_module_dependencies.f90 b/fpm/test/fpm_test/test_module_dependencies.f90 index 7f6c0be..4f2aa27 100644 --- a/fpm/test/fpm_test/test_module_dependencies.f90 +++ b/fpm/test/fpm_test/test_module_dependencies.f90 @@ -39,10 +39,12 @@ contains test_missing_program_use, should_fail=.true.), & & new_unittest("invalid-library-use", & test_invalid_library_use, should_fail=.true.), & - & new_unittest("invalid-own-module-use", & - test_invalid_own_module_use, should_fail=.true.) & + & new_unittest("subdirectory-module-use", & + test_subdirectory_module_use), & + & new_unittest("invalid-subdirectory-module-use", & + test_invalid_subdirectory_module_use, should_fail=.true.) & ] - + end subroutine collect_module_dependencies @@ -62,7 +64,7 @@ contains model%packages(1)%sources(1) = new_test_source(FPM_UNIT_MODULE,file_name="src/my_mod_1.f90", & scope = FPM_SCOPE_LIB, & provides=[string_t('my_mod_1')]) - + model%packages(1)%sources(2) = new_test_source(FPM_UNIT_MODULE,file_name="src/my_mod_2.f90", & scope = FPM_SCOPE_LIB, & provides=[string_t('my_mod_2')], & @@ -82,27 +84,27 @@ contains call check_target(targets(1)%ptr,type=FPM_TARGET_ARCHIVE,n_depends=2, & deps = [targets(2),targets(3)], & links = targets(2:3), error=error) - + if (allocated(error)) return call check_target(targets(2)%ptr,type=FPM_TARGET_OBJECT,n_depends=0, & source=model%packages(1)%sources(1),error=error) - + if (allocated(error)) return - + call check_target(targets(3)%ptr,type=FPM_TARGET_OBJECT,n_depends=1, & deps=[targets(2)],source=model%packages(1)%sources(2),error=error) - + if (allocated(error)) return - + end subroutine test_library_module_use !> Check a program using a library module !> Each program generates two targets: object file and executable - !> + !> subroutine test_program_module_use(error) !> Error handling @@ -128,13 +130,13 @@ contains model%output_directory = '' allocate(model%packages(1)) allocate(model%packages(1)%sources(2)) - + scope_str = merge('FPM_SCOPE_APP ','FPM_SCOPE_TEST',exe_scope==FPM_SCOPE_APP)//' - ' model%packages(1)%sources(1) = new_test_source(FPM_UNIT_MODULE,file_name="src/my_mod_1.f90", & scope = FPM_SCOPE_LIB, & provides=[string_t('my_mod_1')]) - + model%packages(1)%sources(2) = new_test_source(FPM_UNIT_PROGRAM,file_name="app/my_program.f90", & scope=exe_scope, & uses=[string_t('my_mod_1')]) @@ -149,7 +151,7 @@ contains call check_target(targets(1)%ptr,type=FPM_TARGET_ARCHIVE,n_depends=1, & deps=[targets(2)],links=[targets(2)],error=error) - + if (allocated(error)) return call check_target(targets(2)%ptr,type=FPM_TARGET_OBJECT,n_depends=0, & @@ -204,17 +206,17 @@ contains call check_target(targets(1)%ptr,type=FPM_TARGET_OBJECT,n_depends=0, & source=model%packages(1)%sources(1),error=error) - + if (allocated(error)) return call check_target(targets(2)%ptr,type=FPM_TARGET_EXECUTABLE,n_depends=1, & deps=[targets(1)],links=[targets(1)],error=error) - + if (allocated(error)) return - + end subroutine test_program_with_module - + !> Check program using modules in same directory subroutine test_program_own_module_use(error) @@ -246,7 +248,7 @@ contains model%packages(1)%sources(1) = new_test_source(FPM_UNIT_MODULE,file_name="app/app_mod1.f90", & scope = exe_scope, & provides=[string_t('app_mod1')]) - + model%packages(1)%sources(2) = new_test_source(FPM_UNIT_MODULE,file_name="app/app_mod2.f90", & scope = exe_scope, & provides=[string_t('app_mod2')],uses=[string_t('app_mod1')]) @@ -265,17 +267,17 @@ contains call check_target(targets(1)%ptr,type=FPM_TARGET_OBJECT,n_depends=0, & source=model%packages(1)%sources(1),error=error) - + if (allocated(error)) return call check_target(targets(2)%ptr,type=FPM_TARGET_OBJECT,n_depends=1, & source=model%packages(1)%sources(2),deps=[targets(1)],error=error) - + if (allocated(error)) return call check_target(targets(3)%ptr,type=FPM_TARGET_OBJECT,n_depends=1, & source=model%packages(1)%sources(3),deps=[targets(2)],error=error) - + if (allocated(error)) return call check_target(targets(4)%ptr,type=FPM_TARGET_EXECUTABLE,n_depends=1, & @@ -303,14 +305,14 @@ contains model%packages(1)%sources(1) = new_test_source(FPM_UNIT_MODULE,file_name="src/my_mod_1.f90", & scope = FPM_SCOPE_LIB, & provides=[string_t('my_mod_1')]) - + model%packages(1)%sources(2) = new_test_source(FPM_UNIT_MODULE,file_name="src/my_mod_2.f90", & scope = FPM_SCOPE_LIB, & provides=[string_t('my_mod_2')], & uses=[string_t('my_mod_3')]) call targets_from_sources(targets,model,error) - + end subroutine test_missing_library_use @@ -336,7 +338,7 @@ contains uses=[string_t('my_mod_2')]) call targets_from_sources(targets,model,error) - + end subroutine test_missing_program_use @@ -356,19 +358,19 @@ contains model%packages(1)%sources(1) = new_test_source(FPM_UNIT_MODULE,file_name="app/app_mod.f90", & scope = FPM_SCOPE_APP, & provides=[string_t('app_mod')]) - + model%packages(1)%sources(2) = new_test_source(FPM_UNIT_MODULE,file_name="src/my_mod.f90", & scope = FPM_SCOPE_LIB, & provides=[string_t('my_mod')], & uses=[string_t('app_mod')]) call targets_from_sources(targets,model,error) - + end subroutine test_invalid_library_use - !> Check program using a non-library module in a different directory - subroutine test_invalid_own_module_use(error) + !> Check program using a non-library module in a sub-directory + subroutine test_subdirectory_module_use(error) !> Error handling type(error_t), allocatable, intent(out) :: error @@ -383,15 +385,39 @@ contains model%packages(1)%sources(1) = new_test_source(FPM_UNIT_MODULE,file_name="app/subdir/app_mod.f90", & scope = FPM_SCOPE_APP, & provides=[string_t('app_mod')]) - + model%packages(1)%sources(2) = new_test_source(FPM_UNIT_PROGRAM,file_name="app/my_program.f90", & scope=FPM_SCOPE_APP, & uses=[string_t('app_mod')]) call targets_from_sources(targets,model,error) - - end subroutine test_invalid_own_module_use + end subroutine test_subdirectory_module_use + + !> Check program using a non-library module in a differente sub-directory + subroutine test_invalid_subdirectory_module_use(error) + + !> Error handling + type(error_t), allocatable, intent(out) :: error + + type(fpm_model_t) :: model + type(build_target_ptr), allocatable :: targets(:) + + model%output_directory = '' + allocate(model%packages(1)) + allocate(model%packages(1)%sources(2)) + + model%packages(1)%sources(1) = new_test_source(FPM_UNIT_MODULE,file_name="app/diff_dir/app_mod.f90", & + scope = FPM_SCOPE_APP, & + provides=[string_t('app_mod')]) + + model%packages(1)%sources(2) = new_test_source(FPM_UNIT_PROGRAM,file_name="app/prog_dir/my_program.f90", & + scope=FPM_SCOPE_APP, & + uses=[string_t('app_mod')]) + + call targets_from_sources(targets,model,error) + + end subroutine test_invalid_subdirectory_module_use !> Helper to create a new srcfile_t function new_test_source(type,file_name, scope, uses, provides) result(src) @@ -476,7 +502,7 @@ contains call test_failed(error,'There are missing link objects for target "'& //target%output_file//'"') return - + elseif (size(links) < size(target%link_objects)) then call test_failed(error,'There are more link objects than expected for target "'& @@ -523,7 +549,7 @@ contains target_in = .false. do i=1,size(haystack) - + if (associated(haystack(i)%ptr,needle)) then target_in = .true. return @@ -532,6 +558,6 @@ contains end do end function target_in - + end module test_module_dependencies |