aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/fpm.f905
-rw-r--r--src/fpm_compiler.f9025
-rw-r--r--src/fpm_environment.f9021
3 files changed, 26 insertions, 25 deletions
diff --git a/src/fpm.f90 b/src/fpm.f90
index 5854cfb..3310a3f 100644
--- a/src/fpm.f90
+++ b/src/fpm.f90
@@ -4,12 +4,13 @@ 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, get_env, get_archiver
+use fpm_environment, only: run, get_env
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, get_default_c_compiler
+use fpm_compiler, only: get_module_flags, is_unknown_compiler, get_default_c_compiler, &
+ get_archiver
use fpm_sources, only: add_executable_sources, add_sources_from_dir
diff --git a/src/fpm_compiler.f90 b/src/fpm_compiler.f90
index 389ba94..aac6173 100644
--- a/src/fpm_compiler.f90
+++ b/src/fpm_compiler.f90
@@ -27,7 +27,7 @@
! Unisys ? ? ? ? ? discontinued
module fpm_compiler
use fpm_model, only: fpm_model_t
-use fpm_filesystem, only: join_path, basename
+use fpm_filesystem, only: join_path, basename, get_temp_filename
use fpm_environment, only: &
get_os_type, &
OS_LINUX, &
@@ -36,13 +36,15 @@ use fpm_environment, only: &
OS_CYGWIN, &
OS_SOLARIS, &
OS_FREEBSD, &
- OS_OPENBSD
+ OS_OPENBSD, &
+ OS_UNKNOWN
implicit none
public :: is_unknown_compiler
public :: get_module_flags
public :: get_default_compile_flags
public :: get_debug_compile_flags
public :: get_release_compile_flags
+public :: get_archiver
enum, bind(C)
enumerator :: &
@@ -464,4 +466,23 @@ function is_unknown_compiler(compiler) result(is_unknown)
is_unknown = get_compiler_id(compiler) == id_unknown
end function is_unknown_compiler
+
+function get_archiver() result(archiver)
+ character(:), allocatable :: archiver
+ integer :: estat, os_type
+
+ os_type = get_os_type()
+ if (os_type /= OS_WINDOWS .and. os_type /= OS_UNKNOWN) then
+ archiver = "ar -rs "
+ else
+ call execute_command_line("ar --version > "//get_temp_filename(), &
+ & exitstat=estat)
+ if (estat /= 0) then
+ archiver = "lib /OUT:"
+ else
+ archiver = "ar -rs "
+ end if
+ end if
+end function
+
end module fpm_compiler
diff --git a/src/fpm_environment.f90 b/src/fpm_environment.f90
index 3754166..ef0177f 100644
--- a/src/fpm_environment.f90
+++ b/src/fpm_environment.f90
@@ -12,7 +12,6 @@ module fpm_environment
public :: os_is_unix
public :: run
public :: get_env
- public :: get_archiver
public :: get_command_arguments_quoted
public :: separator
@@ -195,26 +194,6 @@ contains
if(VALUE.eq.''.and.present(DEFAULT))VALUE=DEFAULT
end function get_env
- function get_archiver() result(archiver)
- character(:), allocatable :: archiver
-
- associate(os_type => get_os_type())
- if (os_type /= OS_WINDOWS .and. os_type /= OS_UNKNOWN) then
- archiver = "ar -rs "
- else
- block
- integer :: estat
-
- call execute_command_line("ar --version", exitstat=estat)
- if (estat /= 0) then
- archiver = "lib /OUT:"
- else
- archiver = "ar -rs "
- end if
- end block
- end if
- end associate
- end function
function get_command_arguments_quoted() result(args)
character(len=:),allocatable :: args
character(len=:),allocatable :: arg