diff options
author | Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> | 2021-03-31 11:48:00 +0200 |
---|---|---|
committer | GitHub <noreply@github.com> | 2021-03-31 11:48:00 +0200 |
commit | 5422ec57f4081bf2225f5dde5cc07999bf8010f9 (patch) | |
tree | 9f612fed4388f464a434451c84b6645731b07829 | |
parent | a4e8d225184f3bb721528e13a6995de0f920e65b (diff) | |
parent | e0d336ce1aea71693c467367e19bf102f662ec43 (diff) | |
download | fpm-5422ec57f4081bf2225f5dde5cc07999bf8010f9.tar.gz fpm-5422ec57f4081bf2225f5dde5cc07999bf8010f9.zip |
Merge pull request #412 from kubajj/Duplicate_module_definitions
Fix for Issue #396 - Duplicate module definitions
-rw-r--r-- | fpm/src/fpm.f90 | 53 | ||||
-rw-r--r-- | fpm/test/fpm_test/test_module_dependencies.f90 | 105 |
2 files changed, 156 insertions, 2 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index a84bebf..31b68ff 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -23,10 +23,11 @@ use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, & & stdout=>output_unit, & & stderr=>error_unit use fpm_manifest_dependency, only: dependency_config_t +use, intrinsic :: iso_fortran_env, only: error_unit implicit none private public :: cmd_build, cmd_run -public :: build_model +public :: build_model, check_modules_for_duplicates contains @@ -42,6 +43,8 @@ subroutine build_model(model, settings, package, error) integer :: i, j type(package_config_t) :: dependency character(len=:), allocatable :: manifest, lib_dir + + logical :: duplicates_found = .false. type(string_t) :: include_dir model%package_name = package%name @@ -179,8 +182,56 @@ subroutine build_model(model, settings, package, error) write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']' end if + ! Check for duplicate modules + call check_modules_for_duplicates(model, duplicates_found) + if (duplicates_found) then + error stop 'Error: One or more duplicate module names found.' + end if end subroutine build_model +! Check for duplicate modules +subroutine check_modules_for_duplicates(model, duplicates_found) + type(fpm_model_t), intent(in) :: model + integer :: maxsize + integer :: i,j,k,l,m,modi + type(string_t), allocatable :: modules(:) + logical :: duplicates_found + ! Initialise the size of array + maxsize = 0 + ! Get number of modules provided by each source file of every package + do i=1,size(model%packages) + do j=1,size(model%packages(i)%sources) + if (allocated(model%packages(i)%sources(j)%modules_provided)) then + maxsize = maxsize + size(model%packages(i)%sources(j)%modules_provided) + end if + end do + end do + ! Allocate array to contain distinct names of modules + allocate(modules(maxsize)) + + ! Initialise index to point at start of the newly allocated array + modi = 1 + + ! Loop through modules provided by each source file of every package + ! Add it to the array if it is not already there + ! Otherwise print out warning about duplicates + do k=1,size(model%packages) + do l=1,size(model%packages(k)%sources) + if (allocated(model%packages(k)%sources(l)%modules_provided)) then + do m=1,size(model%packages(k)%sources(l)%modules_provided) + if (model%packages(k)%sources(l)%modules_provided(m)%s.in.modules(:modi-1)) then + write(error_unit, *) "Warning: Module ",model%packages(k)%sources(l)%modules_provided(m)%s, & + " in ",model%packages(k)%sources(l)%file_name," is a duplicate" + duplicates_found = .true. + else + modules(modi) = model%packages(k)%sources(l)%modules_provided(m) + modi = modi + 1 + end if + end do + end if + end do + end do +end subroutine check_modules_for_duplicates subroutine cmd_build(settings) type(fpm_build_settings), intent(in) :: settings diff --git a/fpm/test/fpm_test/test_module_dependencies.f90 b/fpm/test/fpm_test/test_module_dependencies.f90 index 4f2aa27..f193646 100644 --- a/fpm/test/fpm_test/test_module_dependencies.f90 +++ b/fpm/test/fpm_test/test_module_dependencies.f90 @@ -10,6 +10,7 @@ module test_module_dependencies FPM_UNIT_CHEADER, FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, & FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_TEST use fpm_strings, only: string_t, operator(.in.) + use fpm, only: check_modules_for_duplicates implicit none private @@ -39,6 +40,14 @@ contains test_missing_program_use, should_fail=.true.), & & new_unittest("invalid-library-use", & test_invalid_library_use, should_fail=.true.), & + & new_unittest("package-with-no-duplicates", & + test_package_with_no_module_duplicates), & + & new_unittest("package-with-duplicates-in-same-source", & + test_package_module_duplicates_same_source, should_fail=.true.), & + & new_unittest("package-with-duplicates-in-one-package", & + test_package_module_duplicates_one_package, should_fail=.true.), & + & new_unittest("package-with-duplicates-in-two-packages", & + test_package_module_duplicates_two_packages, should_fail=.true.), & & new_unittest("subdirectory-module-use", & test_subdirectory_module_use), & & new_unittest("invalid-subdirectory-module-use", & @@ -391,9 +400,103 @@ contains uses=[string_t('app_mod')]) call targets_from_sources(targets,model,error) - + end subroutine test_subdirectory_module_use + !> Check program with no duplicate modules + subroutine test_package_with_no_module_duplicates(error) + + type(error_t), allocatable, intent(out) :: error + + type(fpm_model_t) :: model + logical :: duplicates_found = .false. + + allocate(model%packages(1)) + allocate(model%packages(1)%sources(2)) + + 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')]) + + call check_modules_for_duplicates(model, duplicates_found) + if (duplicates_found) then + call test_failed(error,'Duplicate modules found') + return + end if + end subroutine test_package_with_no_module_duplicates + + !> Check program with duplicate modules in same source file + subroutine test_package_module_duplicates_same_source(error) + + type(error_t), allocatable, intent(out) :: error + + type(fpm_model_t) :: model + logical :: duplicates_found + + allocate(model%packages(1)) + allocate(model%packages(1)%sources(1)) + + 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'), string_t('my_mod_1')]) + + call check_modules_for_duplicates(model, duplicates_found) + if (duplicates_found) then + call test_failed(error,'Duplicate modules found') + return + end if + end subroutine test_package_module_duplicates_same_source + + !> Check program with duplicate modules in two different source files in one package + subroutine test_package_module_duplicates_one_package(error) + + type(error_t), allocatable, intent(out) :: error + + type(fpm_model_t) :: model + logical :: duplicates_found + + allocate(model%packages(1)) + allocate(model%packages(1)%sources(2)) + + model%packages(1)%sources(1) = new_test_source(FPM_UNIT_MODULE,file_name="src/my_mod_1_a.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_1_b.f90", & + scope = FPM_SCOPE_LIB, provides=[string_t('my_mod_1')]) + + call check_modules_for_duplicates(model, duplicates_found) + if (duplicates_found) then + call test_failed(error,'Duplicate modules found') + return + end if + end subroutine test_package_module_duplicates_one_package + + !> Check program with duplicate modules in two different packages + subroutine test_package_module_duplicates_two_packages(error) + + type(error_t), allocatable, intent(out) :: error + + type(fpm_model_t) :: model + logical :: duplicates_found + + allocate(model%packages(2)) + allocate(model%packages(1)%sources(1)) + allocate(model%packages(2)%sources(1)) + + model%packages(1)%sources(1) = new_test_source(FPM_UNIT_MODULE,file_name="src/subdir1/my_mod_1.f90", & + scope = FPM_SCOPE_LIB, provides=[string_t('my_mod_1')]) + + model%packages(2)%sources(1) = new_test_source(FPM_UNIT_MODULE,file_name="src/subdir2/my_mod_1.f90", & + scope = FPM_SCOPE_LIB, provides=[string_t('my_mod_1')]) + + call check_modules_for_duplicates(model, duplicates_found) + if (duplicates_found) then + call test_failed(error,'Duplicate modules found') + return + end if + end subroutine test_package_module_duplicates_two_packages + !> Check program using a non-library module in a differente sub-directory subroutine test_invalid_subdirectory_module_use(error) |