diff options
-rw-r--r-- | bootstrap/src/Fpm.hs | 3 | ||||
-rw-r--r-- | fpm/src/fpm.f90 | 29 | ||||
-rw-r--r-- | fpm/src/fpm_command_line.f90 | 16 | ||||
-rw-r--r-- | fpm/src/fpm_compiler.f90 | 2 | ||||
-rw-r--r-- | fpm/src/fpm_model.f90 | 276 | ||||
-rw-r--r-- | fpm/src/fpm_strings.f90 | 64 | ||||
-rw-r--r-- | fpm/src/fpm_targets.f90 | 91 | ||||
-rw-r--r-- | fpm/test/fpm_test/test_module_dependencies.f90 | 90 |
8 files changed, 454 insertions, 117 deletions
diff --git a/bootstrap/src/Fpm.hs b/bootstrap/src/Fpm.hs index 10e14fe..56e2d90 100644 --- a/bootstrap/src/Fpm.hs +++ b/bootstrap/src/Fpm.hs @@ -681,7 +681,6 @@ defineCompilerSettings specifiedFlags compiler release , "-fmax-errors=1" , "-O3" , "-march=native" - , "-ffast-math" , "-funroll-loops" , "-fcoarray=single" ] @@ -714,7 +713,6 @@ defineCompilerSettings specifiedFlags compiler release , "-fmax-errors=1" , "-O3" , "-march=native" - , "-ffast-math" , "-funroll-loops" ] else @@ -742,7 +740,6 @@ defineCompilerSettings specifiedFlags compiler release , "-Wimplicit-interface" , "-fPIC" , "-fmax-errors=1" - , "-ffast-math" , "-funroll-loops" ] else diff --git a/fpm/src/fpm.f90 b/fpm/src/fpm.f90 index d91b1d4..7609ee0 100644 --- a/fpm/src/fpm.f90 +++ b/fpm/src/fpm.f90 @@ -9,7 +9,7 @@ use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, use fpm_model, only: fpm_model_t, srcfile_t, build_target_t, & FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, & FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST, & - FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE + FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE, show_model use fpm_compiler, only: add_compile_flag_defaults @@ -38,7 +38,6 @@ subroutine build_model(model, settings, package, error) type(fpm_build_settings), intent(in) :: settings type(package_config_t), intent(in) :: package type(error_t), allocatable, intent(out) :: error - type(string_t), allocatable :: package_list(:) integer :: i type(package_config_t) :: dependency @@ -61,10 +60,6 @@ subroutine build_model(model, settings, package, error) call model%deps%add(package, error) if (allocated(error)) return - allocate(package_list(1)) - package_list(1)%s = package%name - - if(settings%compiler.eq.'')then model%fortran_compiler = 'gfortran' else @@ -77,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 @@ -88,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 @@ -97,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 @@ -106,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) @@ -116,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) @@ -126,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) @@ -144,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 @@ -158,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 @@ -199,6 +198,8 @@ if(settings%list)then do i=1,size(model%targets) write(stderr,*) model%targets(i)%ptr%output_file enddo +else if (settings%show_model) then + call show_model(model) else call build_package(model) endif diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90 index 2256530..e569186 100644 --- a/fpm/src/fpm_command_line.f90 +++ b/fpm/src/fpm_command_line.f90 @@ -62,6 +62,7 @@ end type type, extends(fpm_cmd_settings) :: fpm_build_settings logical :: list=.false. + logical :: show_model=.false. character(len=:),allocatable :: compiler character(len=:),allocatable :: build_name end type @@ -187,6 +188,7 @@ contains call set_args( '& & --release F & & --list F & + & --show-model F & & --compiler "'//get_env('FPM_COMPILER','gfortran')//'" & & --verbose F& & --',help_build,version_text) @@ -198,6 +200,7 @@ contains & build_name=val_build,& & compiler=val_compiler, & & list=lget('list'),& + & show_model=lget('show-model'),& & verbose=lget('verbose') ) case('new') @@ -764,14 +767,15 @@ contains ' specified in the "fpm.toml" file. ', & ' ', & 'OPTIONS ', & - ' --release build in build/*_release instead of build/*_debug with ', & - ' high optimization instead of full debug options. ', & - ' --compiler COMPILER_NAME Specify a compiler name. The default is ', & + ' --release build in build/*_release instead of build/*_debug with ', & + ' high optimization instead of full debug options. ', & + ' --compiler COMPILER_NAME Specify a compiler name. The default is ', & ' "gfortran" unless set by the environment ', & ' variable FPM_COMPILER. ', & - ' --list list candidates instead of building or running them ', & - ' --help print this help and exit ', & - ' --version print program version information and exit ', & + ' --list list candidates instead of building or running them ', & + ' --show-model show the model and exit (do not build) ', & + ' --help print this help and exit ', & + ' --version print program version information and exit ', & ' ', & 'EXAMPLES ', & ' Sample commands: ', & diff --git a/fpm/src/fpm_compiler.f90 b/fpm/src/fpm_compiler.f90 index 0265985..ba840e6 100644 --- a/fpm/src/fpm_compiler.f90 +++ b/fpm/src/fpm_compiler.f90 @@ -54,7 +54,6 @@ character(len=:),allocatable :: mandatory ! flags required for fpm to function p & -Wimplicit-interface& & -fPIC& & -fmax-errors=1& - & -ffast-math& & -funroll-loops& &' mandatory=' -J '//modpath//' -I '//modpath @@ -76,7 +75,6 @@ character(len=:),allocatable :: mandatory ! flags required for fpm to function p & -Wimplicit-interface& & -fPIC& & -fmax-errors=1& - & -ffast-math& & -funroll-loops& & -fcoarray=single& &' diff --git a/fpm/src/fpm_model.f90 b/fpm/src/fpm_model.f90 index b7d97db..9c821da 100644 --- a/fpm/src/fpm_model.f90 +++ b/fpm/src/fpm_model.f90 @@ -26,12 +26,13 @@ !> module fpm_model use iso_fortran_env, only: int64 -use fpm_strings, only: string_t +use fpm_strings, only: string_t, str use fpm_dependency, only: dependency_tree_t implicit none private -public :: fpm_model_t, srcfile_t, build_target_t, build_target_ptr +public :: fpm_model_t, srcfile_t, build_target_t, build_target_ptr, & + show_model public :: FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, & FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, & @@ -111,6 +112,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 +171,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(:) @@ -194,4 +207,253 @@ type :: fpm_model_t end type fpm_model_t +contains + +function info_build_target(t) result(s) + type(build_target_t), intent(in) :: t + character(:), allocatable :: s + integer :: i + !type build_target_t + s = "build_target_t(" + ! character(:), allocatable :: output_file + s = s // 'output_file="' // t%output_file // '"' + ! type(srcfile_t), allocatable :: source + if (allocated(t%source)) then + s = s // ", source=" // info_srcfile_short(t%source) + else + s = s // ", source=()" + end if + ! type(build_target_ptr), allocatable :: dependencies(:) + s = s // ", dependencies=[" + if (allocated(t%dependencies)) then + do i = 1, size(t%dependencies) + s = s // info_build_target_short(t%dependencies(i)%ptr) + if (i < size(t%dependencies)) s = s // ", " + end do + end if + s = s // "]" + ! integer :: target_type = FPM_TARGET_UNKNOWN + s = s // ", target_type=" + select case(t%target_type) + case (FPM_TARGET_UNKNOWN) + s = s // "FPM_TARGET_UNKNOWN" + case (FPM_TARGET_EXECUTABLE) + s = s // "FPM_TARGET_EXECUTABLE" + case (FPM_TARGET_ARCHIVE) + s = s // "FPM_TARGET_ARCHIVE" + case (FPM_TARGET_OBJECT) + s = s // "FPM_TARGET_OBJECT" + case default + s = s // "INVALID" + end select + ! type(string_t), allocatable :: link_libraries(:) + s = s // ", link_libraries=[" + if (allocated(t%link_libraries)) then + do i = 1, size(t%link_libraries) + s = s // '"' // t%link_libraries(i)%s // '"' + if (i < size(t%link_libraries)) s = s // ", " + end do + end if + s = s // "]" + ! type(string_t), allocatable :: link_objects(:) + s = s // ", link_objects=[" + if (allocated(t%link_objects)) then + do i = 1, size(t%link_objects) + s = s // '"' // t%link_objects(i)%s // '"' + if (i < size(t%link_objects)) s = s // ", " + end do + end if + s = s // "]" + ! logical :: touched = .false. + s = s // ", touched=" // str(t%touched) + ! logical :: sorted = .false. + s = s // ", sorted=" // str(t%sorted) + ! logical :: skip = .false. + s = s // ", skip=" // str(t%skip) + ! integer :: schedule = -1 + s = s // ", schedule=" // str(t%schedule) + ! integer(int64), allocatable :: digest_cached + if (allocated(t%digest_cached)) then + s = s // ", digest_cached=" // str(t%digest_cached) + else + s = s // ", digest_cached=()" + end if + !end type build_target_t + s = s // ")" +end function info_build_target + +function info_build_target_short(t) result(s) + ! Prints a shortened representation of build_target_t + type(build_target_t), intent(in) :: t + character(:), allocatable :: s + integer :: i + s = "build_target_t(" + s = s // 'output_file="' // t%output_file // '"' + s = s // ", ...)" +end function info_build_target_short + +function info_package(p) result(s) + ! Returns representation of package_t + type(package_t), intent(in) :: p + character(:), allocatable :: s + + integer :: i + + s = s // 'package_t(' + s = s // 'name="' // p%name //'"' + s = s // ', sources=[' + do i = 1, size(p%sources) + s = s // info_srcfile(p%sources(i)) + if (i < size(p%sources)) s = s // ", " + end do + s = s // "]" + s = s // ")" + +end function info_package + +function info_srcfile(source) result(s) + type(srcfile_t), intent(in) :: source + character(:), allocatable :: s + integer :: i + !type srcfile_t + s = "srcfile_t(" + ! character(:), allocatable :: file_name + s = s // 'file_name="' // source%file_name // '"' + ! character(:), allocatable :: exe_name + s = s // ', exe_name="' // source%exe_name // '"' + ! integer :: unit_scope = FPM_SCOPE_UNKNOWN + s = s // ", unit_scope=" + select case(source%unit_scope) + case (FPM_SCOPE_UNKNOWN) + s = s // "FPM_SCOPE_UNKNOWN" + case (FPM_SCOPE_LIB) + s = s // "FPM_SCOPE_LIB" + case (FPM_SCOPE_DEP) + s = s // "FPM_SCOPE_DEP" + case (FPM_SCOPE_APP) + s = s // "FPM_SCOPE_APP" + case (FPM_SCOPE_TEST) + s = s // "FPM_SCOPE_TEST" + case (FPM_SCOPE_EXAMPLE) + s = s // "FPM_SCOPE_EXAMPLE" + case default + s = s // "INVALID" + end select + ! type(string_t), allocatable :: modules_provided(:) + s = s // ", modules_provided=[" + do i = 1, size(source%modules_provided) + s = s // '"' // source%modules_provided(i)%s // '"' + if (i < size(source%modules_provided)) s = s // ", " + end do + s = s // "]" + ! integer :: unit_type = FPM_UNIT_UNKNOWN + s = s // ", unit_type=" + select case(source%unit_type) + case (FPM_UNIT_UNKNOWN) + s = s // "FPM_UNIT_UNKNOWN" + case (FPM_UNIT_PROGRAM) + s = s // "FPM_UNIT_PROGRAM" + case (FPM_UNIT_MODULE) + s = s // "FPM_UNIT_MODULE" + case (FPM_UNIT_SUBMODULE) + s = s // "FPM_UNIT_SUBMODULE" + case (FPM_UNIT_SUBPROGRAM) + s = s // "FPM_UNIT_SUBPROGRAM" + case (FPM_UNIT_CSOURCE) + s = s // "FPM_UNIT_CSOURCE" + case (FPM_UNIT_CHEADER) + s = s // "FPM_UNIT_CHEADER" + case default + s = s // "INVALID" + end select + ! type(string_t), allocatable :: modules_used(:) + s = s // ", modules_used=[" + do i = 1, size(source%modules_used) + s = s // '"' // source%modules_used(i)%s // '"' + if (i < size(source%modules_used)) s = s // ", " + end do + s = s // "]" + ! type(string_t), allocatable :: include_dependencies(:) + s = s // ", include_dependencies=[" + do i = 1, size(source%include_dependencies) + s = s // '"' // source%include_dependencies(i)%s // '"' + if (i < size(source%include_dependencies)) s = s // ", " + end do + s = s // "]" + ! type(string_t), allocatable :: link_libraries(:) + s = s // ", link_libraries=[" + do i = 1, size(source%link_libraries) + s = s // '"' // source%link_libraries(i)%s // '"' + if (i < size(source%link_libraries)) s = s // ", " + end do + s = s // "]" + ! integer(int64) :: digest + s = s // ", digest=" // str(source%digest) + !end type srcfile_t + s = s // ")" +end function info_srcfile + +function info_srcfile_short(source) result(s) + ! Prints a shortened version of srcfile_t + type(srcfile_t), intent(in) :: source + character(:), allocatable :: s + integer :: i + s = "srcfile_t(" + s = s // 'file_name="' // source%file_name // '"' + s = s // ", ...)" +end function info_srcfile_short + +function info_model(model) result(s) + type(fpm_model_t), intent(in) :: model + character(:), allocatable :: s + integer :: i + !type :: fpm_model_t + s = "fpm_model_t(" + ! character(:), allocatable :: package_name + s = s // 'package_name="' // model%package_name // '"' + ! type(srcfile_t), allocatable :: sources(:) + s = s // ", packages=[" + do i = 1, size(model%packages) + s = s // info_package(model%packages(i)) + if (i < size(model%packages)) s = s // ", " + end do + s = s // "]" + ! type(build_target_ptr), allocatable :: targets(:) + s = s // ", targets=[" + do i = 1, size(model%targets) + s = s // info_build_target(model%targets(i)%ptr) + if (i < size(model%targets)) s = s // ", " + end do + s = s // "]" + ! character(:), allocatable :: fortran_compiler + s = s // ', fortran_compiler="' // model%fortran_compiler // '"' + ! character(:), allocatable :: fortran_compile_flags + s = s // ', fortran_compile_flags="' // model%fortran_compile_flags // '"' + ! character(:), allocatable :: link_flags + s = s // ', link_flags="' // model%link_flags // '"' + ! character(:), allocatable :: library_file + s = s // ', library_file="' // model%library_file // '"' + ! character(:), allocatable :: output_directory + s = s // ', output_directory="' // model%output_directory // '"' + ! type(string_t), allocatable :: link_libraries(:) + s = s // ", link_libraries=[" + do i = 1, size(model%link_libraries) + s = s // '"' // model%link_libraries(i)%s // '"' + if (i < size(model%link_libraries)) s = s // ", " + end do + s = s // "]" + ! type(dependency_tree_t) :: deps + ! TODO: print `dependency_tree_t` properly, which should become part of the + ! model, not imported from another file + s = s // ", deps=dependency_tree_t(...)" + !end type fpm_model_t + s = s // ")" +end function info_model + +subroutine show_model(model) + ! Prints a human readable representation of the Model + type(fpm_model_t), intent(in) :: model + print *, info_model(model) +end subroutine show_model + end module fpm_model diff --git a/fpm/src/fpm_strings.f90 b/fpm/src/fpm_strings.f90 index 649be36..4c18b59 100644 --- a/fpm/src/fpm_strings.f90 +++ b/fpm/src/fpm_strings.f90 @@ -5,8 +5,7 @@ implicit none private public :: f_string, lower, split, str_ends_with, string_t public :: string_array_contains, string_cat, operator(.in.), fnv_1a -public :: resize -public :: join +public :: resize, str, join type string_t character(len=:), allocatable :: s @@ -30,6 +29,10 @@ interface str_ends_with procedure :: str_ends_with_any end interface str_ends_with +interface str + module procedure str_int, str_int64, str_logical +end interface + contains pure logical function str_ends_with_str(s, e) result(r) @@ -452,5 +455,62 @@ character(len=:),allocatable :: sep_local, left_local, right_local endif enddo end function join +======= +pure integer function str_int_len(i) result(sz) +! Returns the length of the string representation of 'i' +integer, intent(in) :: i +integer, parameter :: MAX_STR = 100 +character(MAX_STR) :: s +! If 's' is too short (MAX_STR too small), Fortran will abort with: +! "Fortran runtime error: End of record" +write(s, '(i0)') i +sz = len_trim(s) +end function + +pure function str_int(i) result(s) +! Converts integer "i" to string +integer, intent(in) :: i +character(len=str_int_len(i)) :: s +write(s, '(i0)') i +end function + +pure integer function str_int64_len(i) result(sz) +! Returns the length of the string representation of 'i' +integer(int64), intent(in) :: i +integer, parameter :: MAX_STR = 100 +character(MAX_STR) :: s +! If 's' is too short (MAX_STR too small), Fortran will abort with: +! "Fortran runtime error: End of record" +write(s, '(i0)') i +sz = len_trim(s) +end function + +pure function str_int64(i) result(s) +! Converts integer "i" to string +integer(int64), intent(in) :: i +character(len=str_int64_len(i)) :: s +write(s, '(i0)') i +end function + +pure integer function str_logical_len(l) result(sz) +! Returns the length of the string representation of 'l' +logical, intent(in) :: l +if (l) then + sz = 6 +else + sz = 7 +end if +end function + +pure function str_logical(l) result(s) +! Converts logical "l" to string +logical, intent(in) :: l +character(len=str_logical_len(l)) :: s +if (l) then + s = ".true." +else + s = ".false." +end if +end function end module fpm_strings diff --git a/fpm/src/fpm_targets.f90 b/fpm/src/fpm_targets.f90 index 34f437f..c2615a0 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 |