aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--fpm/src/fpm.f9037
1 files changed, 37 insertions, 0 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90
index 68385cd..ee07100 100644
--- a/fpm/src/fpm.f90
+++ b/fpm/src/fpm.f90
@@ -154,8 +154,45 @@ subroutine build_model(model, settings, package, error)
end do
if (allocated(error)) return
+ ! Check for duplicate modules
+ call check_modules(model)
end subroutine build_model
+! Check for duplicate modules
+subroutine check_modules(model)
+ type(fpm_model_t), intent(in) :: model
+ integer :: maxsize
+ integer :: i,j,k,modi
+ type(string_t), allocatable :: modules(:)
+ ! Initialise the size of array
+ maxsize = 0
+ ! Get number of modules provided by each source file
+ do i=1,size(model%packages(1)%sources)
+ if (allocated(model%packages(1)%sources(j)%modules_provided)) then
+ maxsize = maxsize + size(model%packages(1)%sources(i)%modules_provided)
+ end if
+ end do
+ ! Allocate array to contain distinct names of modules
+ allocate(modules(1:maxsize))
+
+ ! Initialise index to point at start of the newly allocated array
+ modi = 1
+
+ ! Loop through modules provided by each source file
+ ! Add it to the array if it is not already there
+ ! Otherwise print out warning about duplicates
+ do j=1,size(model%packages(1)%sources)
+ if (allocated(model%packages(1)%sources(j)%modules_provided)) then
+ do k=1,size(model%packages(1)%sources(j)%modules_provided)
+ if (model%packages(1)%sources(j)%modules_provided(k)%s.in.modules) then
+ print *,"Warning: Module ",model%packages(1)%sources(j)%modules_provided(k)%s," is duplicate"
+ else
+ modules(modi) = model%packages(1)%sources(j)%modules_provided(k)
+ end if
+ end do
+ end if
+ end do
+end subroutine check_modules
subroutine cmd_build(settings)
type(fpm_build_settings), intent(in) :: settings