@@ -18,7 +18,7 @@ module fpm
1818 resolve_target_linking, build_target_t, build_target_ptr, &
1919 FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE
2020use fpm_manifest, only : get_package_data, package_config_t
21- use fpm_error, only : error_t, fatal_error
21+ use fpm_error, only : error_t, fatal_error, fpm_stop
2222use fpm_manifest_test, only : test_config_t
2323use ,intrinsic :: iso_fortran_env, only : stdin= >input_unit, &
2424 & stdout= >output_unit, &
@@ -196,7 +196,7 @@ subroutine build_model(model, settings, package, error)
196196 ! Check for duplicate modules
197197 call check_modules_for_duplicates(model, duplicates_found)
198198 if (duplicates_found) then
199- error stop ' Error: One or more duplicate module names found.'
199+ call fpm_stop( 1 , ' *build_model*: Error: One or more duplicate module names found.' )
200200 end if
201201end subroutine build_model
202202
@@ -255,20 +255,17 @@ subroutine cmd_build(settings)
255255
256256call get_package_data(package, " fpm.toml" , error, apply_defaults= .true. )
257257if (allocated (error)) then
258- print ' (a)' , error% message
259- error stop 1
258+ call fpm_stop(1 ,' *cmd_build*:package error:' // error% message)
260259end if
261260
262261call build_model(model, settings, package, error)
263262if (allocated (error)) then
264- print ' (a)' , error% message
265- error stop 1
263+ call fpm_stop(1 ,' *cmd_build*:model error:' // error% message)
266264end if
267265
268266call targets_from_sources(targets,model,error)
269267if (allocated (error)) then
270- print ' (a)' , error% message
271- error stop 1
268+ call fpm_stop(1 ,' *cmd_build*:target error:' // error% message)
272269end if
273270
274271if (settings% list)then
@@ -304,20 +301,17 @@ subroutine cmd_run(settings,test)
304301
305302 call get_package_data(package, " fpm.toml" , error, apply_defaults= .true. )
306303 if (allocated (error)) then
307- print ' (a)' , error% message
308- error stop 1
304+ call fpm_stop(1 , ' *cmd_run*:package error:' // error% message)
309305 end if
310306
311307 call build_model(model, settings% fpm_build_settings, package, error)
312308 if (allocated (error)) then
313- print ' (a)' , error% message
314- error stop 1
309+ call fpm_stop(1 , ' *cmd_run*:model error:' // error% message)
315310 end if
316311
317312 call targets_from_sources(targets,model,error)
318313 if (allocated (error)) then
319- print ' (a)' , error% message
320- error stop 1
314+ call fpm_stop(1 , ' *cmd_run*:targets error:' // error% message)
321315 end if
322316
323317 if (test) then
@@ -373,11 +367,10 @@ subroutine cmd_run(settings,test)
373367 ! Check if any apps/tests were found
374368 if (col_width < 0 ) then
375369 if (test) then
376- write (stderr, * ) ' No tests to run'
370+ call fpm_stop( 0 , ' No tests to run' )
377371 else
378- write (stderr, * ) ' No executables to run'
372+ call fpm_stop( 0 , ' No executables to run' )
379373 end if
380- stop
381374 end if
382375
383376 ! Check all names are valid
@@ -391,7 +384,7 @@ subroutine cmd_run(settings,test)
391384 line= join(settings% name)
392385 if (line.ne. ' .' )then ! do not report these special strings
393386 if (any (.not. found))then
394- write (stderr,' (A)' ,advance= " no" )' fpm::run <ERROR> specified names '
387+ write (stderr,' (A)' ,advance= " no" )' <ERROR>*cmd_run*: specified names '
395388 do j= 1 ,size (settings% name)
396389 if (.not. found(j)) write (stderr,' (A)' ,advance= " no" ) ' "' // trim (settings% name (j))// ' " '
397390 end do
@@ -406,9 +399,9 @@ subroutine cmd_run(settings,test)
406399 call compact_list_all()
407400
408401 if (line.eq. ' .' .or. line.eq. ' ' )then ! do not report these special strings
409- stop
402+ call fpm_stop( 0 , ' ' )
410403 else
411- stop 1
404+ call fpm_stop( 1 , ' ' )
412405 endif
413406
414407 end if
@@ -430,18 +423,17 @@ subroutine cmd_run(settings,test)
430423 exitstat= stat(i))
431424 endif
432425 else
433- write (stderr,* )' fpm::run<ERROR>' ,executables(i)% s,' not found'
434- stop 1
426+ call fpm_stop(1 ,' *cmd_run*:' // executables(i)% s// ' not found' )
435427 end if
436428 end do
437429
438430 if (any (stat /= 0 )) then
439431 do i= 1 ,size (stat)
440432 if (stat(i) /= 0 ) then
441- write (* , * ) ' <ERROR> Execution failed for "' ,basename(executables(i)% s),' "'
433+ write (stderr, ' (*(g0:,1x)) ' ) ' <ERROR> Execution failed for object "' ,basename(executables(i)% s),' "'
442434 end if
443435 end do
444- stop 1
436+ call fpm_stop( 1 , ' *cmd_run*:stopping due to failed executions ' )
445437 end if
446438
447439 endif
0 commit comments