Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
5 changes: 3 additions & 2 deletions src/fpm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4,12 +4,13 @@ module fpm
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
Expand Down
25 changes: 23 additions & 2 deletions src/fpm_compiler.f90
Original file line number Diff line number Diff line change
Expand Up @@ -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, &
Expand All @@ -36,13 +36,15 @@ module fpm_compiler
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 :: &
Expand Down Expand Up @@ -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()//" 2>&1", &
& exitstat=estat)
if (estat /= 0) then
archiver = "lib /OUT:"
else
archiver = "ar -rs "
end if
end if
end function

end module fpm_compiler
21 changes: 0 additions & 21 deletions src/fpm_environment.f90
Original file line number Diff line number Diff line change
Expand Up @@ -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

Expand Down Expand Up @@ -195,26 +194,6 @@ function get_env(NAME,DEFAULT) result(VALUE)
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
Expand Down