aboutsummaryrefslogtreecommitdiff
path: root/src/fpm.f90
diff options
context:
space:
mode:
authorJohn S. Urban <urbanjost@comcast.net>2021-07-11 16:11:39 -0400
committerJohn S. Urban <urbanjost@comcast.net>2021-07-11 16:11:39 -0400
commitcca5f83be11f40dd2be86671f8ec14a429540cc9 (patch)
treeebffeeddffd608f82db70d8683ca68ef22688d67 /src/fpm.f90
parentf452d20faec8827347f5e6783cb8dfa325c1c301 (diff)
downloadfpm-cca5f83be11f40dd2be86671f8ec14a429540cc9.tar.gz
fpm-cca5f83be11f40dd2be86671f8ec14a429540cc9.zip
all stops via fpm_stop(1)
Diffstat (limited to 'src/fpm.f90')
-rw-r--r--src/fpm.f9040
1 files changed, 16 insertions, 24 deletions
diff --git a/src/fpm.f90 b/src/fpm.f90
index bc6741d..d32051b 100644
--- a/src/fpm.f90
+++ b/src/fpm.f90
@@ -18,7 +18,7 @@ use fpm_targets, only: targets_from_sources, resolve_module_dependencies, &
resolve_target_linking, build_target_t, build_target_ptr, &
FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE
use fpm_manifest, only : get_package_data, package_config_t
-use fpm_error, only : error_t, fatal_error
+use fpm_error, only : error_t, fatal_error, fpm_stop
use fpm_manifest_test, only : test_config_t
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
& stdout=>output_unit, &
@@ -196,7 +196,7 @@ subroutine build_model(model, settings, package, error)
! Check for duplicate modules
call check_modules_for_duplicates(model, duplicates_found)
if (duplicates_found) then
- error stop 'Error: One or more duplicate module names found.'
+ call fpm_stop(1,'*build_model*:Error: One or more duplicate module names found.')
end if
end subroutine build_model
@@ -255,20 +255,17 @@ integer :: i
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
if (allocated(error)) then
- print '(a)', error%message
- stop 1
+ call fpm_stop(1,'*cmd_build*:package error:'//error%message)
end if
call build_model(model, settings, package, error)
if (allocated(error)) then
- print '(a)', error%message
- stop 1
+ call fpm_stop(1,'*cmd_build*:model error:'//error%message)
end if
call targets_from_sources(targets,model,error)
if (allocated(error)) then
- print '(a)', error%message
- stop 1
+ call fpm_stop(1,'*cmd_build*:target error:'//error%message)
end if
if(settings%list)then
@@ -304,20 +301,17 @@ subroutine cmd_run(settings,test)
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
if (allocated(error)) then
- print '(a)', error%message
- stop 1
+ call fpm_stop(1, '*cmd_run*:package error:'//error%message)
end if
call build_model(model, settings%fpm_build_settings, package, error)
if (allocated(error)) then
- print '(a)', error%message
- stop 1
+ call fpm_stop(1, '*cmd_run*:model error:'//error%message)
end if
call targets_from_sources(targets,model,error)
if (allocated(error)) then
- print '(a)', error%message
- stop 1
+ call fpm_stop(1, '*cmd_run*:targets error:'//error%message)
end if
if (test) then
@@ -373,11 +367,10 @@ subroutine cmd_run(settings,test)
! Check if any apps/tests were found
if (col_width < 0) then
if (test) then
- write(stderr,*) 'No tests to run'
+ call fpm_stop(0,'No tests to run')
else
- write(stderr,*) 'No executables to run'
+ call fpm_stop(0,'No executables to run')
end if
- stop
end if
! Check all names are valid
@@ -391,7 +384,7 @@ subroutine cmd_run(settings,test)
line=join(settings%name)
if(line.ne.'.')then ! do not report these special strings
if(any(.not.found))then
- write(stderr,'(A)',advance="no")'fpm::run<ERROR> specified names '
+ write(stderr,'(A)',advance="no")'<ERROR>*cmd_run*:specified names '
do j=1,size(settings%name)
if (.not.found(j)) write(stderr,'(A)',advance="no") '"'//trim(settings%name(j))//'" '
end do
@@ -406,9 +399,9 @@ subroutine cmd_run(settings,test)
call compact_list_all()
if(line.eq.'.' .or. line.eq.' ')then ! do not report these special strings
- stop
+ call fpm_stop(0,'')
else
- stop 1
+ call fpm_stop(1,'')
endif
end if
@@ -430,18 +423,17 @@ subroutine cmd_run(settings,test)
exitstat=stat(i))
endif
else
- write(stderr,*)'fpm::run<ERROR>',executables(i)%s,' not found'
- stop 1
+ call fpm_stop(1,'*cmd_run*:'//executables(i)%s//' not found')
end if
end do
if (any(stat /= 0)) then
do i=1,size(stat)
if (stat(i) /= 0) then
- write(*,*) '<ERROR> Execution failed for "',basename(executables(i)%s),'"'
+ write(stderr,'(*(g0:,1x))') '<ERROR> Execution failed for object "',basename(executables(i)%s),'"'
end if
end do
- stop 1
+ call fpm_stop(1,'*cmd_run*:stopping due to failed executions')
end if
endif