aboutsummaryrefslogtreecommitdiff
path: root/src/fpm.f90
diff options
context:
space:
mode:
authorLKedward <laurence.kedward@bristol.ac.uk>2021-06-05 14:37:40 +0100
committerLKedward <laurence.kedward@bristol.ac.uk>2021-06-05 14:37:40 +0100
commit7e9c3390b04a0fc746812abd65a574a9dd219c81 (patch)
tree66a5df663bf46aa1df7c8cf174f10902ac06f1e1 /src/fpm.f90
parent086ae55dfa09c1924d2b54bc88ddb1827f9dcfa7 (diff)
parent845217f13a23de91021ba393ef432d68683af282 (diff)
downloadfpm-7e9c3390b04a0fc746812abd65a574a9dd219c81.tar.gz
fpm-7e9c3390b04a0fc746812abd65a574a9dd219c81.zip
Merge branch 'upstream_master' into backend-grace
Diffstat (limited to 'src/fpm.f90')
-rw-r--r--src/fpm.f9028
1 files changed, 19 insertions, 9 deletions
diff --git a/src/fpm.f90 b/src/fpm.f90
index 31b68ff..5854cfb 100644
--- a/src/fpm.f90
+++ b/src/fpm.f90
@@ -4,12 +4,12 @@ use fpm_backend, only: build_package
use fpm_command_line, only: fpm_build_settings, fpm_new_settings, &
fpm_run_settings, fpm_install_settings, fpm_test_settings
use fpm_dependency, only : new_dependency_tree
-use fpm_environment, only: run
+use fpm_environment, only: run, get_env, get_archiver
use fpm_filesystem, only: is_dir, join_path, number_of_rows, list_files, exists, basename
use fpm_model, only: fpm_model_t, srcfile_t, show_model, &
FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, FPM_SCOPE_DEP, &
FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST
-use fpm_compiler, only: get_module_flags, is_unknown_compiler
+use fpm_compiler, only: get_module_flags, is_unknown_compiler, get_default_c_compiler
use fpm_sources, only: add_executable_sources, add_sources_from_dir
@@ -51,6 +51,7 @@ subroutine build_model(model, settings, package, error)
allocate(model%include_dirs(0))
allocate(model%link_libraries(0))
+ allocate(model%external_modules(0))
call new_dependency_tree(model%deps, cache=join_path("build", "cache.toml"))
call model%deps%add(package, error)
@@ -62,6 +63,10 @@ subroutine build_model(model, settings, package, error)
model%fortran_compiler = settings%compiler
endif
+ model%archiver = get_archiver()
+ call get_default_c_compiler(model%fortran_compiler, model%c_compiler)
+ model%c_compiler = get_env('FPM_C_COMPILER',model%c_compiler)
+
if (is_unknown_compiler(model%fortran_compiler)) then
write(*, '(*(a:,1x))') &
"<WARN>", "Unknown compiler", model%fortran_compiler, "requested!", &
@@ -147,7 +152,7 @@ subroutine build_model(model, settings, package, error)
if (.not.allocated(model%packages(i)%sources)) allocate(model%packages(i)%sources(0))
if (allocated(dependency%library)) then
-
+
if (allocated(dependency%library%source_dir)) then
lib_dir = join_path(dep%proj_dir, dependency%library%source_dir)
if (is_dir(lib_dir)) then
@@ -165,12 +170,16 @@ subroutine build_model(model, settings, package, error)
end if
end do
end if
-
+
end if
if (allocated(dependency%build%link)) then
model%link_libraries = [model%link_libraries, dependency%build%link]
end if
+
+ if (allocated(dependency%build%external_modules)) then
+ model%external_modules = [model%external_modules, dependency%build%external_modules]
+ end if
end associate
end do
if (allocated(error)) return
@@ -178,8 +187,9 @@ subroutine build_model(model, settings, package, error)
if (settings%verbose) then
write(*,*)'<INFO> BUILD_NAME: ',settings%build_name
write(*,*)'<INFO> COMPILER: ',settings%compiler
- write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
- write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
+ write(*,*)'<INFO> C COMPILER: ',model%c_compiler
+ write(*,*)'<INFO> COMPILER OPTIONS: ', model%fortran_compile_flags
+ write(*,*)'<INFO> INCLUDE DIRECTORIES: [', string_cat(model%include_dirs,','),']'
end if
! Check for duplicate modules
@@ -190,7 +200,7 @@ subroutine build_model(model, settings, package, error)
end subroutine build_model
! Check for duplicate modules
-subroutine check_modules_for_duplicates(model, duplicates_found)
+subroutine check_modules_for_duplicates(model, duplicates_found)
type(fpm_model_t), intent(in) :: model
integer :: maxsize
integer :: i,j,k,l,m,modi
@@ -370,7 +380,7 @@ subroutine cmd_run(settings,test)
! Check all names are valid
! or no name and found more than one file
- toomany= size(settings%name).eq.0 .and. size(executables).gt.1
+ toomany= size(settings%name).eq.0 .and. size(executables).gt.1
if ( any(.not.found) &
& .or. &
& ( (toomany .and. .not.test) .or. (toomany .and. settings%runner .ne. '') ) &
@@ -420,7 +430,7 @@ subroutine cmd_run(settings,test)
end if
end do
endif
- contains
+ contains
subroutine compact_list_all()
integer, parameter :: LINE_WIDTH = 80
integer :: i, j, nCol