diff options
author | Jakub JelĂnek <33724536+kubajj@users.noreply.github.com> | 2021-03-30 21:34:09 +0200 |
---|---|---|
committer | GitHub <noreply@github.com> | 2021-03-30 21:34:09 +0200 |
commit | 7d9a4f6412b3f56d7b52196cbe63a1507e650afc (patch) | |
tree | 69a4a37a438d35de1371c0e3b02d97cc99258c74 | |
parent | d7850f0d395f6d426a4fafebc10d058cfd9f549d (diff) | |
parent | 799fcacee02e60a1679116765c4c3669d31e7201 (diff) | |
download | fpm-7d9a4f6412b3f56d7b52196cbe63a1507e650afc.tar.gz fpm-7d9a4f6412b3f56d7b52196cbe63a1507e650afc.zip |
Merge branch 'master' into Duplicate_module_definitions
-rw-r--r-- | README.md | 6 | ||||
-rw-r--r-- | fpm/fpm.toml | 2 | ||||
-rw-r--r-- | fpm/src/fpm_command_line.f90 | 2 | ||||
-rw-r--r-- | fpm/src/fpm_source_parsing.f90 | 3 | ||||
-rw-r--r-- | fpm/src/fpm_strings.f90 | 115 | ||||
-rw-r--r-- | fpm/src/fpm_targets.f90 | 66 | ||||
-rw-r--r-- | fpm/test/fpm_test/test_module_dependencies.f90 | 95 |
7 files changed, 157 insertions, 132 deletions
@@ -5,20 +5,20 @@ Its key goal is to improve the user experience of Fortran programmers. It does so by making it easier to build your Fortran program or library, run the executables, tests, and examples, and distribute it as a dependency to other Fortran projects. -Fpm's user interface is modeled after [Rust's Cargo](https://crates.io/), +Fpm's user interface is modeled after [Rust's Cargo](https://doc.rust-lang.org/cargo/), so if you're familiar with that tool, you will feel at home with fpm. Fpm's long term vision is to nurture and grow the ecosystem of modern Fortran applications and libraries. Fpm is an early prototype and is evolving rapidly. You can use it to build and package your Fortran projects, as well as to use -existing fpm packages as dependencies. +[existing fpm packages](https://github.com/fortran-lang/fpm-registry) as dependencies. Fpm's behavior and user interface may change as it evolves, however as fpm matures and we enter production, we will aim to stay backwards compatible. Please follow the [issues](https://github.com/fortran-lang/fpm/issues) to contribute and/or stay up to date with the development. Before opening a bug report or a feature suggestion, please read our -[Contributor Guide](CONTRIBUTING.md). +[Contributor Guide](CONTRIBUTING.md). You can also discuss your ideas and queries with the community in [fpm discussions](https://github.com/fortran-lang/fpm/discussions), or more broadly on [Fortran-Lang Discourse](https://fortran-lang.discourse.group/) Fortran Package Manager is not to be confused with [Jordan Sissel's fpm](https://github.com/jordansissel/fpm), a more general, diff --git a/fpm/fpm.toml b/fpm/fpm.toml index e28f2bc..4bd2d96 100644 --- a/fpm/fpm.toml +++ b/fpm/fpm.toml @@ -1,5 +1,5 @@ name = "fpm" -version = "0.1.4" +version = "0.2.0" license = "MIT" author = "fpm maintainers" maintainer = "" diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index b986cf7..9e9a572 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -133,7 +133,7 @@ contains case default ; os_type = "OS Type: UNKNOWN" end select version_text = [character(len=80) :: & - & 'Version: 0.1.4, alpha', & + & 'Version: 0.2.0, alpha', & & 'Program: fpm(1)', & & 'Description: A Fortran package manager and build system', & & 'Home Page: https://github.com/fortran-lang/fpm', & diff --git a/fpm/src/fpm_source_parsing.f90 b/fpm/src/fpm_source_parsing.f90 index 76cb560..dd9a4c5 100644 --- a/fpm/src/fpm_source_parsing.f90 +++ b/fpm/src/fpm_source_parsing.f90 @@ -33,7 +33,8 @@ character(15), parameter :: INTRINSIC_MODULE_NAMES(*) = & 'iso_fortran_env', & 'ieee_arithmetic', & 'ieee_exceptions', & - 'ieee_features '] + 'ieee_features ', & + 'omp_lib '] contains diff --git a/fpm/src/fpm_strings.f90 b/fpm/src/fpm_strings.f90 index d62a370..3d7d7b1 100644 --- a/fpm/src/fpm_strings.f90 +++ b/fpm/src/fpm_strings.f90 @@ -431,12 +431,13 @@ end subroutine resize_string !>AUTHOR: John S. Urban !!LICENSE: Public Domain -!!## NAME -!! join(3f) - [fpm_strings:EDITING] append CHARACTER variable array into +!> +!!##NAME +!! join(3f) - [M_strings:EDITING] append CHARACTER variable array into !! a single CHARACTER variable with specified separator !! (LICENSE:PD) !! -!!## SYNOPSIS +!!##SYNOPSIS !! !! pure function join(str,sep,trm,left,right,start,end) result (string) !! @@ -449,13 +450,13 @@ end subroutine resize_string !! character(len=*),intent(in),optional :: end !! character(len=:),allocatable :: string !! -!!## DESCRIPTION +!!##DESCRIPTION !! JOIN(3f) appends the elements of a CHARACTER array into a single !! CHARACTER variable, with elements 1 to N joined from left to right. !! By default each element is trimmed of trailing spaces and the !! default separator is a null string. !! -!!## OPTIONS +!!##OPTIONS !! STR(:) array of CHARACTER variables to be joined !! SEP separator string to place between each variable. defaults !! to a null string. @@ -466,81 +467,75 @@ end subroutine resize_string !! TRM option to trim each element of STR of trailing !! spaces. Defaults to .TRUE. !! -!!## RESULT +!!##RESULT !! STRING CHARACTER variable composed of all of the elements of STR() !! appended together with the optional separator SEP placed !! between the elements. !! -!!## EXAMPLE +!!##EXAMPLE !! !! Sample program: -!!```fortran -!! program demo_join -!! use fpm_strings, only: join -!! implicit none -!! character(len=:),allocatable :: s(:) -!! character(len=:),allocatable :: out -!! integer :: i -!! s=[character(len=10) :: 'United',' we',' stand,', & -!! & ' divided',' we fall.'] -!! out=join(s) -!! write(*,'(a)') out -!! write(*,'(a)') join(s,trm=.false.) -!! write(*,'(a)') (join(s,trm=.false.,sep='|'),i=1,3) -!! write(*,'(a)') join(s,sep='<>') -!! write(*,'(a)') join(s,sep=';',left='[',right=']') -!! write(*,'(a)') join(s,left='[',right=']') -!! write(*,'(a)') join(s,left='>>') -!! end program demo_join -!!```fortran !! -!! Expected output: +!! program demo_join +!! use M_strings, only: join +!! implicit none +!! character(len=:),allocatable :: s(:) +!! character(len=:),allocatable :: out +!! integer :: i +!! s=[character(len=10) :: 'United',' we',' stand,', & +!! & ' divided',' we fall.'] +!! out=join(s) +!! write(*,'(a)') out +!! write(*,'(a)') join(s,trm=.false.) +!! write(*,'(a)') (join(s,trm=.false.,sep='|'),i=1,3) +!! write(*,'(a)') join(s,sep='<>') +!! write(*,'(a)') join(s,sep=';',left='[',right=']') +!! write(*,'(a)') join(s,left='[',right=']') +!! write(*,'(a)') join(s,left='>>') +!! end program demo_join !! -!! United we stand, divided we fall. -!! United we stand, divided we fall. -!! United | we | stand, | divided | we fall. -!! United | we | stand, | divided | we fall. -!! United | we | stand, | divided | we fall. -!! United<> we<> stand,<> divided<> we fall. -!! [United];[ we];[ stand,];[ divided];[ we fall.] -!! [United][ we][ stand,][ divided][ we fall.] -!! >>United>> we>> stand,>> divided>> we fall. +!! Expected output: !! +!! United we stand, divided we fall. +!! United we stand, divided we fall. +!! United | we | stand, | divided | we fall. +!! United | we | stand, | divided | we fall. +!! United | we | stand, | divided | we fall. +!! United<> we<> stand,<> divided<> we fall. +!! [United];[ we];[ stand,];[ divided];[ we fall.] +!! [United][ we][ stand,][ divided][ we fall.] +!! >>United>> we>> stand,>> divided>> we fall. pure function join(str,sep,trm,left,right,start,end) result (string) -! @(#)join(3f): append an array of character variables with specified separator into a single CHARACTER variable +! @(#)M_strings::join(3f): merge string array into a single CHARACTER value adding specified separators, caps, prefix and suffix character(len=*),intent(in) :: str(:) -character(len=*),intent(in),optional :: sep -character(len=*),intent(in),optional :: right -character(len=*),intent(in),optional :: left -character(len=*),intent(in),optional :: start -character(len=*),intent(in),optional :: end +character(len=*),intent(in),optional :: sep, right, left, start, end logical,intent(in),optional :: trm +character(len=:),allocatable :: sep_local, left_local, right_local character(len=:),allocatable :: string -integer :: i logical :: trm_local -character(len=:),allocatable :: sep_local -character(len=:),allocatable :: left_local -character(len=:),allocatable :: right_local - - if(present(sep))then ; sep_local=sep ; else ; sep_local='' ; endif - if(present(trm))then ; trm_local=trm ; else ; trm_local=.true. ; endif - if(present(left))then ; left_local=left ; else ; left_local='' ; endif - if(present(right))then ; right_local=right ; else ; right_local='' ; endif - +integer :: i + if(present(sep))then ; sep_local=sep ; else ; sep_local='' ; endif + if(present(trm))then ; trm_local=trm ; else ; trm_local=.true. ; endif + if(present(left))then ; left_local=left ; else ; left_local='' ; endif + if(present(right))then ; right_local=right ; else ; right_local='' ; endif string='' - do i = 1,size(str)-1 + if(size(str).eq.0)then + string=string//left_local//right_local + else + do i = 1,size(str)-1 + if(trm_local)then + string=string//left_local//trim(str(i))//right_local//sep_local + else + string=string//left_local//str(i)//right_local//sep_local + endif + enddo if(trm_local)then - string=string//left_local//trim(str(i))//right_local//sep_local + string=string//left_local//trim(str(i))//right_local else - string=string//left_local//str(i)//right_local//sep_local + string=string//left_local//str(i)//right_local endif - enddo - if(trm_local)then - string=string//left_local//trim(str(i))//right_local - else - string=string//left_local//str(i)//right_local endif if(present(start))string=start//string if(present(end))string=string//end 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 fc580bc..fe92aab 100644 --- a/fpm/test/fpm_test/test_module_dependencies.f90 +++ b/fpm/test/fpm_test/test_module_dependencies.f90 @@ -51,9 +51,13 @@ contains & 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.) & + test_package_module_duplicates_two_packages, 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 @@ -73,7 +77,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')], & @@ -93,27 +97,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 @@ -139,13 +143,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')]) @@ -160,7 +164,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, & @@ -215,17 +219,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) @@ -257,7 +261,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')]) @@ -276,17 +280,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, & @@ -314,14 +318,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 @@ -347,7 +351,7 @@ contains uses=[string_t('my_mod_2')]) call targets_from_sources(targets,model,error) - + end subroutine test_missing_program_use @@ -367,19 +371,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 @@ -394,14 +398,12 @@ 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 !> Check program with no duplicate modules subroutine test_package_with_no_module_duplicates(error) @@ -496,6 +498,33 @@ contains return end if end subroutine test_package_module_duplicates_two_packages + + 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) @@ -580,7 +609,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 "'& @@ -627,7 +656,7 @@ contains target_in = .false. do i=1,size(haystack) - + if (associated(haystack(i)%ptr,needle)) then target_in = .true. return @@ -636,6 +665,6 @@ contains end do end function target_in - + end module test_module_dependencies |