diff options
author | kubajj <vilouskubajj@gmail.com> | 2021-03-30 21:30:39 +0200 |
---|---|---|
committer | kubajj <vilouskubajj@gmail.com> | 2021-03-30 21:30:39 +0200 |
commit | 12d1bcc7e305a736f3ec7ffd70d722da4355131b (patch) | |
tree | a2f6fe6c12d436b60aa668838a8f40645f183cb3 | |
parent | aa7eca7b9bb2344fbc60567c102e3cf413a77453 (diff) | |
download | fpm-12d1bcc7e305a736f3ec7ffd70d722da4355131b.tar.gz fpm-12d1bcc7e305a736f3ec7ffd70d722da4355131b.zip |
Add simple tests for the module duplicates
-rw-r--r-- | fpm/src/fpm.f90 | 2 | ||||
-rw-r--r-- | fpm/test/fpm_test/test_module_dependencies.f90 | 106 |
2 files changed, 106 insertions, 2 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index 0c8dcd9..e201648 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -27,7 +27,7 @@ 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 diff --git a/fpm/test/fpm_test/test_module_dependencies.f90 b/fpm/test/fpm_test/test_module_dependencies.f90 index 7f6c0be..fc580bc 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 @@ -40,7 +41,17 @@ contains & 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.) & + test_invalid_own_module_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-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.) & ] end subroutine collect_module_dependencies @@ -392,6 +403,99 @@ contains end subroutine test_invalid_own_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 + + 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 !> Helper to create a new srcfile_t function new_test_source(type,file_name, scope, uses, provides) result(src) |