diff options
-rw-r--r-- | fpm/src/fpm.f90 | 20 | ||||
-rw-r--r-- | fpm/src/fpm_model.f90 | 22 | ||||
-rw-r--r-- | fpm/src/fpm_targets.f90 | 91 | ||||
-rw-r--r-- | fpm/test/fpm_test/test_module_dependencies.f90 | 90 |
4 files changed, 127 insertions, 96 deletions
diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index 8dd8c17..aa86787 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -72,9 +72,11 @@ subroutine build_model(model, settings, package, error) model%link_flags = '' + allocate(model%packages(model%deps%ndep)) + ! Add sources from executable directories if (is_dir('app') .and. package%build%auto_executables) then - call add_sources_from_dir(model%sources,'app', FPM_SCOPE_APP, & + call add_sources_from_dir(model%packages(1)%sources,'app', FPM_SCOPE_APP, & with_executables=.true., error=error) if (allocated(error)) then @@ -83,7 +85,7 @@ subroutine build_model(model, settings, package, error) end if if (is_dir('example') .and. package%build%auto_examples) then - call add_sources_from_dir(model%sources,'example', FPM_SCOPE_EXAMPLE, & + call add_sources_from_dir(model%packages(1)%sources,'example', FPM_SCOPE_EXAMPLE, & with_executables=.true., error=error) if (allocated(error)) then @@ -92,7 +94,7 @@ subroutine build_model(model, settings, package, error) end if if (is_dir('test') .and. package%build%auto_tests) then - call add_sources_from_dir(model%sources,'test', FPM_SCOPE_TEST, & + call add_sources_from_dir(model%packages(1)%sources,'test', FPM_SCOPE_TEST, & with_executables=.true., error=error) if (allocated(error)) then @@ -101,7 +103,7 @@ subroutine build_model(model, settings, package, error) end if if (allocated(package%executable)) then - call add_executable_sources(model%sources, package%executable, FPM_SCOPE_APP, & + call add_executable_sources(model%packages(1)%sources, package%executable, FPM_SCOPE_APP, & auto_discover=package%build%auto_executables, & error=error) @@ -111,7 +113,7 @@ subroutine build_model(model, settings, package, error) end if if (allocated(package%example)) then - call add_executable_sources(model%sources, package%example, FPM_SCOPE_EXAMPLE, & + call add_executable_sources(model%packages(1)%sources, package%example, FPM_SCOPE_EXAMPLE, & auto_discover=package%build%auto_examples, & error=error) @@ -121,7 +123,7 @@ subroutine build_model(model, settings, package, error) end if if (allocated(package%test)) then - call add_executable_sources(model%sources, package%test, FPM_SCOPE_TEST, & + call add_executable_sources(model%packages(1)%sources, package%test, FPM_SCOPE_TEST, & auto_discover=package%build%auto_tests, & error=error) @@ -139,9 +141,11 @@ subroutine build_model(model, settings, package, error) apply_defaults=.true.) if (allocated(error)) exit + model%packages(i)%name = dependency%name + if (allocated(dependency%library)) then lib_dir = join_path(dep%proj_dir, dependency%library%source_dir) - call add_sources_from_dir(model%sources, lib_dir, FPM_SCOPE_LIB, & + call add_sources_from_dir(model%packages(i)%sources, lib_dir, FPM_SCOPE_LIB, & error=error) if (allocated(error)) exit end if @@ -153,7 +157,7 @@ subroutine build_model(model, settings, package, error) end do if (allocated(error)) return - call targets_from_sources(model,model%sources) + call targets_from_sources(model) do i = 1, size(model%link_libraries) model%link_flags = model%link_flags // " -l" // model%link_libraries(i)%s diff --git a/fpm/src/fpm_model.f90 b/fpm/src/fpm_model.f90 index b7d97db..fba1983 100644 --- a/fpm/src/fpm_model.f90 +++ b/fpm/src/fpm_model.f90 @@ -111,6 +111,18 @@ type srcfile_t end type srcfile_t +!> Type for describing a single package +type package_t + + !> Name of package + character(:), allocatable :: name + + !> Array of sources + type(srcfile_t), allocatable :: sources(:) + +end type package_t + + !> Wrapper type for constructing arrays of `[[build_target_t]]` pointers type build_target_ptr @@ -158,15 +170,15 @@ type build_target_t end type build_target_t -!> Type describing everything required to build a package -!> and its dependencies. +!> Type describing everything required to build +!> the root package and its dependencies. type :: fpm_model_t - !> Name of package + !> Name of root package character(:), allocatable :: package_name - !> Array of sources - type(srcfile_t), allocatable :: sources(:) + !> Array of packages (including the root package) + type(package_t), allocatable :: packages(:) !> Array of targets with module-dependencies resolved type(build_target_ptr), allocatable :: targets(:) diff --git a/fpm/src/fpm_targets.f90 b/fpm/src/fpm_targets.f90 index 34f437f..a9c80f7 100644 --- a/fpm/src/fpm_targets.f90 +++ b/fpm/src/fpm_targets.f90 @@ -53,15 +53,12 @@ contains !> !> @note Inter-object dependencies based on modules used and provided are generated separately !> in `[[resolve_module_dependencies]]` after all targets have been enumerated. -subroutine targets_from_sources(model,sources) +subroutine targets_from_sources(model) !> The package model within which to construct the target list type(fpm_model_t), intent(inout), target :: model - !> The list of sources from which to construct the target list - type(srcfile_t), intent(in) :: sources(:) - - integer :: i + integer :: i, j character(:), allocatable :: xsuffix, exe_dir type(build_target_t), pointer :: dep logical :: with_lib @@ -72,61 +69,71 @@ subroutine targets_from_sources(model,sources) xsuffix = '' end if - with_lib = any([(sources(i)%unit_scope == FPM_SCOPE_LIB,i=1,size(sources))]) + with_lib = any([((model%packages(j)%sources(i)%unit_scope == FPM_SCOPE_LIB, & + i=1,size(model%packages(j)%sources)) & + ,j=1,size(model%packages))]) if (with_lib) call add_target(model%targets,type = FPM_TARGET_ARCHIVE,& output_file = join_path(model%output_directory,& model%package_name,'lib'//model%package_name//'.a')) - do i=1,size(sources) + do j=1,size(model%packages) - select case (sources(i)%unit_type) - case (FPM_UNIT_MODULE,FPM_UNIT_SUBMODULE,FPM_UNIT_SUBPROGRAM,FPM_UNIT_CSOURCE) + associate(sources=>model%packages(j)%sources) - call add_target(model%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(model%targets(1)%ptr, model%targets(size(model%targets))%ptr) - end if + 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(model%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(model%targets(1)%ptr, model%targets(size(model%targets))%ptr) + end if - case (FPM_UNIT_PROGRAM) + case (FPM_UNIT_PROGRAM) - call add_target(model%targets,type = FPM_TARGET_OBJECT,& - output_file = get_object_name(sources(i)), & - source = sources(i) & - ) - - if (sources(i)%unit_scope == FPM_SCOPE_APP) then + call add_target(model%targets,type = FPM_TARGET_OBJECT,& + output_file = get_object_name(sources(i)), & + source = sources(i) & + ) + + if (sources(i)%unit_scope == FPM_SCOPE_APP) then - exe_dir = 'app' + exe_dir = 'app' - else if (sources(i)%unit_scope == FPM_SCOPE_EXAMPLE) then + else if (sources(i)%unit_scope == FPM_SCOPE_EXAMPLE) then - exe_dir = 'example' + exe_dir = 'example' - else + else - exe_dir = 'test' + exe_dir = 'test' - end if + end if - call add_target(model%targets,type = FPM_TARGET_EXECUTABLE,& - link_libraries = sources(i)%link_libraries, & - output_file = join_path(model%output_directory,exe_dir, & - sources(i)%exe_name//xsuffix)) + call add_target(model%targets,type = FPM_TARGET_EXECUTABLE,& + link_libraries = sources(i)%link_libraries, & + output_file = join_path(model%output_directory,exe_dir, & + sources(i)%exe_name//xsuffix)) - ! Executable depends on object - call add_dependency(model%targets(size(model%targets))%ptr, model%targets(size(model%targets)-1)%ptr) + ! Executable depends on object + call add_dependency(model%targets(size(model%targets))%ptr, model%targets(size(model%targets)-1)%ptr) - if (with_lib) then - ! Executable depends on library - call add_dependency(model%targets(size(model%targets))%ptr, model%targets(1)%ptr) - end if - - end select + if (with_lib) then + ! Executable depends on library + call add_dependency(model%targets(size(model%targets))%ptr, model%targets(1)%ptr) + end if + + end select + + end do + + 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 5d78e0c..0635350 100644 --- a/fpm/test/fpm_test/test_module_dependencies.f90 +++ b/fpm/test/fpm_test/test_module_dependencies.f90 @@ -52,21 +52,22 @@ contains !> Error handling type(error_t), allocatable, intent(out) :: error - type(srcfile_t) :: sources(2) type(fpm_model_t) :: model model%output_directory = '' + allocate(model%packages(1)) + allocate(model%packages(1)%sources(2)) - sources(1) = new_test_source(FPM_UNIT_MODULE,file_name="src/my_mod_1.f90", & + 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')]) - sources(2) = new_test_source(FPM_UNIT_MODULE,file_name="src/my_mod_2.f90", & + 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_1')]) - call targets_from_sources(model,sources) + call targets_from_sources(model) call resolve_module_dependencies(model%targets,error) if (allocated(error)) then @@ -87,13 +88,13 @@ contains call check_target(model%targets(2)%ptr,type=FPM_TARGET_OBJECT,n_depends=0, & - source=sources(1),error=error) + source=model%packages(1)%sources(1),error=error) if (allocated(error)) return call check_target(model%targets(3)%ptr,type=FPM_TARGET_OBJECT,n_depends=1, & - deps=[model%targets(2)],source=sources(2),error=error) + deps=[model%targets(2)],source=model%packages(1)%sources(2),error=error) if (allocated(error)) return @@ -121,23 +122,24 @@ contains type(error_t), allocatable, intent(out) :: error integer :: i - type(srcfile_t) :: sources(3) type(fpm_model_t) :: model character(:), allocatable :: scope_str 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)//' - ' - sources(1) = new_test_source(FPM_UNIT_MODULE,file_name="src/my_mod_1.f90", & + 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')]) - sources(2) = new_test_source(FPM_UNIT_PROGRAM,file_name="app/my_program.f90", & + 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')]) - call targets_from_sources(model,sources) + call targets_from_sources(model) call resolve_module_dependencies(model%targets,error) if (allocated(error)) then @@ -157,12 +159,12 @@ contains if (allocated(error)) return call check_target(model%targets(2)%ptr,type=FPM_TARGET_OBJECT,n_depends=0, & - source=sources(1),error=error) + source=model%packages(1)%sources(1),error=error) if (allocated(error)) return call check_target(model%targets(3)%ptr,type=FPM_TARGET_OBJECT,n_depends=1, & - deps=[model%targets(2)],source=sources(2),error=error) + deps=[model%targets(2)],source=model%packages(1)%sources(2),error=error) if (allocated(error)) return @@ -185,17 +187,18 @@ contains type(error_t), allocatable, intent(out) :: error integer :: i - type(srcfile_t) :: sources(1) type(fpm_model_t) :: model model%output_directory = '' + allocate(model%packages(1)) + allocate(model%packages(1)%sources(1)) - sources(1) = new_test_source(FPM_UNIT_PROGRAM,file_name="app/my_program.f90", & + model%packages(1)%sources(1) = new_test_source(FPM_UNIT_PROGRAM,file_name="app/my_program.f90", & scope = FPM_SCOPE_APP, & provides=[string_t('app_mod')], & uses=[string_t('app_mod')]) - call targets_from_sources(model,sources) + call targets_from_sources(model) call resolve_module_dependencies(model%targets,error) if (allocated(error)) then @@ -211,7 +214,7 @@ contains call resolve_target_linking(model%targets) call check_target(model%targets(1)%ptr,type=FPM_TARGET_OBJECT,n_depends=0, & - source=sources(1),error=error) + source=model%packages(1)%sources(1),error=error) if (allocated(error)) return @@ -241,27 +244,28 @@ contains integer, intent(in) :: exe_scope type(error_t), allocatable, intent(out) :: error - type(srcfile_t) :: sources(3) type(fpm_model_t) :: model character(:), allocatable :: scope_str model%output_directory = '' + allocate(model%packages(1)) + allocate(model%packages(1)%sources(3)) scope_str = merge('FPM_SCOPE_APP ','FPM_SCOPE_TEST',exe_scope==FPM_SCOPE_APP)//' - ' - sources(1) = new_test_source(FPM_UNIT_MODULE,file_name="app/app_mod1.f90", & + 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')]) - sources(2) = new_test_source(FPM_UNIT_MODULE,file_name="app/app_mod2.f90", & + 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')]) - sources(3) = new_test_source(FPM_UNIT_PROGRAM,file_name="app/my_program.f90", & + model%packages(1)%sources(3) = new_test_source(FPM_UNIT_PROGRAM,file_name="app/my_program.f90", & scope=exe_scope, & uses=[string_t('app_mod2')]) - call targets_from_sources(model,sources) + call targets_from_sources(model) call resolve_module_dependencies(model%targets,error) if (allocated(error)) then @@ -276,17 +280,17 @@ contains call resolve_target_linking(model%targets) call check_target(model%targets(1)%ptr,type=FPM_TARGET_OBJECT,n_depends=0, & - source=sources(1),error=error) + source=model%packages(1)%sources(1),error=error) if (allocated(error)) return call check_target(model%targets(2)%ptr,type=FPM_TARGET_OBJECT,n_depends=1, & - source=sources(2),deps=[model%targets(1)],error=error) + source=model%packages(1)%sources(2),deps=[model%targets(1)],error=error) if (allocated(error)) return call check_target(model%targets(3)%ptr,type=FPM_TARGET_OBJECT,n_depends=1, & - source=sources(3),deps=[model%targets(2)],error=error) + source=model%packages(1)%sources(3),deps=[model%targets(2)],error=error) if (allocated(error)) return @@ -305,21 +309,22 @@ contains !> Error handling type(error_t), allocatable, intent(out) :: error - type(srcfile_t) :: sources(2) type(fpm_model_t) :: model model%output_directory = '' + allocate(model%packages(1)) + allocate(model%packages(1)%sources(2)) - sources(1) = new_test_source(FPM_UNIT_MODULE,file_name="src/my_mod_1.f90", & + 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')]) - sources(2) = new_test_source(FPM_UNIT_MODULE,file_name="src/my_mod_2.f90", & + 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(model,sources) + call targets_from_sources(model) call resolve_module_dependencies(model%targets,error) end subroutine test_missing_library_use @@ -331,20 +336,21 @@ contains !> Error handling type(error_t), allocatable, intent(out) :: error - type(srcfile_t) :: sources(2) type(fpm_model_t) :: model model%output_directory = '' + allocate(model%packages(1)) + allocate(model%packages(1)%sources(2)) - sources(1) = new_test_source(FPM_UNIT_MODULE,file_name="src/my_mod_1.f90", & + 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')]) - sources(2) = new_test_source(FPM_UNIT_PROGRAM,file_name="app/my_program.f90", & + model%packages(1)%sources(2) = new_test_source(FPM_UNIT_PROGRAM,file_name="app/my_program.f90", & scope=FPM_SCOPE_APP, & uses=[string_t('my_mod_2')]) - call targets_from_sources(model,sources) + call targets_from_sources(model) call resolve_module_dependencies(model%targets,error) end subroutine test_missing_program_use @@ -356,21 +362,22 @@ contains !> Error handling type(error_t), allocatable, intent(out) :: error - type(srcfile_t) :: sources(2) type(fpm_model_t) :: model model%output_directory = '' + allocate(model%packages(1)) + allocate(model%packages(1)%sources(2)) - sources(1) = new_test_source(FPM_UNIT_MODULE,file_name="app/app_mod.f90", & + 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')]) - sources(2) = new_test_source(FPM_UNIT_MODULE,file_name="src/my_mod.f90", & + 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(model,sources) + call targets_from_sources(model) call resolve_module_dependencies(model%targets,error) end subroutine test_invalid_library_use @@ -382,20 +389,21 @@ contains !> Error handling type(error_t), allocatable, intent(out) :: error - type(srcfile_t) :: sources(2) type(fpm_model_t) :: model model%output_directory = '' + allocate(model%packages(1)) + allocate(model%packages(1)%sources(2)) - sources(1) = new_test_source(FPM_UNIT_MODULE,file_name="app/subdir/app_mod.f90", & + 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')]) - sources(2) = new_test_source(FPM_UNIT_PROGRAM,file_name="app/my_program.f90", & + 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(model,sources) + call targets_from_sources(model) call resolve_module_dependencies(model%targets,error) end subroutine test_invalid_own_module_use |