aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorLaurence Kedward <laurence.kedward@bristol.ac.uk>2021-11-22 16:12:14 +0000
committerLaurence Kedward <laurence.kedward@bristol.ac.uk>2021-11-22 16:22:31 +0000
commit6ea34933fbb991df706d613718acfefee538efdc (patch)
tree2617722ffbdd870bb3bc2f087c65f237adef0c2a
parent30d730f51fea587574a922f8763f3c7988198029 (diff)
downloadfpm-6ea34933fbb991df706d613718acfefee538efdc.tar.gz
fpm-6ea34933fbb991df706d613718acfefee538efdc.zip
Update: fpm_compiler objects with verbose field
-rw-r--r--src/fpm.f905
-rw-r--r--src/fpm_compiler.f9016
2 files changed, 16 insertions, 5 deletions
diff --git a/src/fpm.f90 b/src/fpm.f90
index 0fec0ed..8b05a38 100644
--- a/src/fpm.f90
+++ b/src/fpm.f90
@@ -62,6 +62,11 @@ subroutine build_model(model, settings, package, error)
call new_compiler(model%compiler, settings%compiler, settings%c_compiler)
call new_archiver(model%archiver, settings%archiver)
+ model%compiler%verbose = settings%verbose
+ model%compiler%echo = settings%verbose
+ model%archiver%verbose = settings%verbose
+ model%archiver%echo = settings%verbose
+
if (settings%flag == '') then
flags = model%compiler%get_default_flags(settings%profile == "release")
else
diff --git a/src/fpm_compiler.f90 b/src/fpm_compiler.f90
index c0c5b73..e83d7a4 100644
--- a/src/fpm_compiler.f90
+++ b/src/fpm_compiler.f90
@@ -79,6 +79,8 @@ type :: compiler_t
character(len=:), allocatable :: cc
!> Print all commands
logical :: echo = .true.
+ !> Verbose output of command
+ logical :: verbose = .true.
contains
!> Get default compiler flags
procedure :: get_default_flags
@@ -107,6 +109,8 @@ type :: archiver_t
logical :: use_response_file = .false.
!> Print all command
logical :: echo = .true.
+ !> Verbose output of command
+ logical :: verbose = .true.
contains
!> Create static archive
procedure :: make_archive
@@ -695,7 +699,7 @@ subroutine compile_fortran(self, input, output, args, stat)
integer, intent(out) :: stat
call run(self%fc // " -c " // input // " " // args // " -o " // output, &
- & echo=self%echo, exitstat=stat)
+ & echo=self%echo, verbose=self%verbose, exitstat=stat)
end subroutine compile_fortran
@@ -713,7 +717,7 @@ subroutine compile_c(self, input, output, args, stat)
integer, intent(out) :: stat
call run(self%cc // " -c " // input // " " // args // " -o " // output, &
- & echo=self%echo, exitstat=stat)
+ & echo=self%echo, verbose=self%verbose, exitstat=stat)
end subroutine compile_c
@@ -728,7 +732,8 @@ subroutine link(self, output, args, stat)
!> Status flag
integer, intent(out) :: stat
- call run(self%fc // " " // args // " -o " // output, echo=self%echo, exitstat=stat)
+ call run(self%fc // " " // args // " -o " // output, echo=self%echo, &
+ & verbose=self%verbose, exitstat=stat)
end subroutine link
@@ -745,11 +750,12 @@ subroutine make_archive(self, output, args, stat)
if (self%use_response_file) then
call write_response_file(output//".resp" , args)
- call run(self%ar // output // " @" // output//".resp", echo=self%echo, exitstat=stat)
+ call run(self%ar // output // " @" // output//".resp", echo=self%echo, &
+ & verbose=self%verbose, exitstat=stat)
call delete_file(output//".resp")
else
call run(self%ar // output // " " // string_cat(args, " "), &
- & echo=self%echo, exitstat=stat)
+ & echo=self%echo, verbose=self%verbose, exitstat=stat)
end if
end subroutine make_archive