Skip to content

Commit cca5f83

Browse files
committed
all stops via fpm_stop(1)
1 parent f452d20 commit cca5f83

File tree

9 files changed

+57
-48
lines changed

9 files changed

+57
-48
lines changed

src/fpm.f90

Lines changed: 16 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ module fpm
1818
resolve_target_linking, build_target_t, build_target_ptr, &
1919
FPM_TARGET_EXECUTABLE, FPM_TARGET_ARCHIVE
2020
use 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
2222
use fpm_manifest_test, only : test_config_t
2323
use,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
201201
end subroutine build_model
202202

@@ -255,20 +255,17 @@ subroutine cmd_build(settings)
255255

256256
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
257257
if (allocated(error)) then
258-
print '(a)', error%message
259-
stop 1
258+
call fpm_stop(1,'*cmd_build*:package error:'//error%message)
260259
end if
261260

262261
call build_model(model, settings, package, error)
263262
if (allocated(error)) then
264-
print '(a)', error%message
265-
stop 1
263+
call fpm_stop(1,'*cmd_build*:model error:'//error%message)
266264
end if
267265

268266
call targets_from_sources(targets,model,error)
269267
if (allocated(error)) then
270-
print '(a)', error%message
271-
stop 1
268+
call fpm_stop(1,'*cmd_build*:target error:'//error%message)
272269
end if
273270

274271
if(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-
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-
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-
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

src/fpm/cmd/install.f90

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@ module fpm_cmd_install
33
use fpm, only : build_model
44
use fpm_backend, only : build_package
55
use fpm_command_line, only : fpm_install_settings
6-
use fpm_error, only : error_t, fatal_error
6+
use fpm_error, only : error_t, fatal_error, fpm_stop
77
use fpm_filesystem, only : join_path, list_files
88
use fpm_installer, only : installer_t, new_installer
99
use fpm_manifest, only : package_config_t, get_package_data
@@ -168,8 +168,7 @@ end function is_module_file
168168
subroutine handle_error(error)
169169
type(error_t), intent(in), optional :: error
170170
if (present(error)) then
171-
print '("[Error]", 1x, a)', error%message
172-
stop 1
171+
call fpm_stop(1,error%message)
173172
end if
174173
end subroutine handle_error
175174

src/fpm/cmd/new.f90

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -58,6 +58,7 @@ module fpm_cmd_new
5858
use fpm_filesystem, only : join_path, exists, basename, mkdir, is_dir
5959
use fpm_filesystem, only : fileopen, fileclose, filewrite, warnwrite
6060
use fpm_strings, only : join, to_fortran_name
61+
use fpm_error, only : fpm_stop
6162
use,intrinsic :: iso_fortran_env, only : stderr=>error_unit
6263
implicit none
6364
private
@@ -606,7 +607,7 @@ subroutine create_verified_basic_manifest(filename)
606607
! continue building of manifest
607608
! ...
608609
call new_package(package, table, error=error)
609-
if (allocated(error)) stop 3
610+
if (allocated(error)) call fpm_stop( 3,'')
610611
if(settings%verbose)then
611612
call table%accept(ser)
612613
endif

src/fpm/cmd/update.f90

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
module fpm_cmd_update
22
use fpm_command_line, only : fpm_update_settings
33
use fpm_dependency, only : dependency_tree_t, new_dependency_tree
4-
use fpm_error, only : error_t
4+
use fpm_error, only : error_t, fpm_stop
55
use fpm_filesystem, only : exists, mkdir, join_path, delete_file
66
use fpm_manifest, only : package_config_t, get_package_data
77
implicit none
@@ -60,8 +60,7 @@ subroutine handle_error(error)
6060
!> Potential error
6161
type(error_t), intent(in), optional :: error
6262
if (present(error)) then
63-
print '(a)', error%message
64-
stop 1
63+
call fpm_stop(1, error%message)
6564
end if
6665
end subroutine handle_error
6766

src/fpm/error.f90

Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
!> Implementation of basic error handling.
22
module fpm_error
3+
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
34
use fpm_strings, only : is_fortran_name, to_fortran_name
45
implicit none
56
private
@@ -8,6 +9,7 @@ module fpm_error
89
public :: fatal_error, syntax_error, file_not_found_error
910
public :: file_parse_error
1011
public :: bad_name_error
12+
public :: fpm_stop
1113

1214

1315
!> Data type defining an error
@@ -155,5 +157,23 @@ subroutine file_parse_error(error, file_name, message, line_num, &
155157

156158
end subroutine file_parse_error
157159

160+
subroutine fpm_stop(value,message)
161+
! TODO: if verbose mode, call ERROR STOP instead of STOP
162+
! TODO: if M_escape is used, add color
163+
! to work with older compilers might need a case statement for values
164+
165+
!> value to use on STOP
166+
integer, intent(in) :: value
167+
!> Error message
168+
character(len=*), intent(in) :: message
169+
if(message.ne.'')then
170+
if(value.gt.0)then
171+
write(stderr,'("<ERROR>",a)')trim(message)
172+
else
173+
write(stderr,'("<INFO> ",a)')trim(message)
174+
endif
175+
endif
176+
stop value
177+
end subroutine fpm_stop
158178

159179
end module fpm_error

src/fpm_backend.f90

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,8 @@
2727
!>
2828
module fpm_backend
2929

30+
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
31+
use fpm_error, only : fpm_stop
3032
use fpm_environment, only: run, get_os_type, OS_WINDOWS
3133
use fpm_filesystem, only: basename, dirname, join_path, exists, mkdir, unix_path
3234
use fpm_model, only: fpm_model_t
@@ -98,10 +100,10 @@ subroutine build_package(targets,model)
98100
if (build_failed) then
99101
do j=1,size(stat)
100102
if (stat(j) /= 0) then
101-
write(*,*) '<ERROR> Compilation failed for object "',basename(queue(j)%ptr%output_file),'"'
103+
write(stderr,'(*(g0:,1x))') '<ERROR> Compilation failed for object "',basename(queue(j)%ptr%output_file),'"'
102104
end if
103105
end do
104-
stop 1
106+
call fpm_stop(1,'stopping due to failed compilation')
105107
end if
106108

107109
end do
@@ -135,8 +137,7 @@ recursive subroutine sort_target(target)
135137
! Check for a circular dependency
136138
! (If target has been touched but not processed)
137139
if (target%touched) then
138-
write(*,*) '(!) Circular dependency found with: ',target%output_file
139-
stop
140+
call fpm_stop(1,'(!) Circular dependency found with: '//target%output_file)
140141
else
141142
target%touched = .true. ! Set touched flag
142143
end if

src/fpm_command_line.f90

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -138,7 +138,8 @@ subroutine get_command_line_settings(cmd_settings)
138138
case default ; os_type = "OS Type: UNKNOWN"
139139
end select
140140
version_text = [character(len=80) :: &
141-
& 'Version: 0.3.0, alpha', &
141+
& 'Version: 0.3.0, alpha', &
142+
& 'PR: 511', &
142143
& 'Program: fpm(1)', &
143144
& 'Description: A Fortran package manager and build system', &
144145
& 'Home Page: https://github.com/fortran-lang/fpm', &

src/fpm_filesystem.f90

Lines changed: 7 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,13 @@
11
!> This module contains general routines for interacting with the file system
22
!!
33
module fpm_filesystem
4-
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
4+
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, stderr=>error_unit
55
use fpm_environment, only: get_os_type, &
66
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
77
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
88
use fpm_environment, only: separator, get_env
99
use fpm_strings, only: f_string, replace, string_t, split
10+
use fpm_error, only : fpm_stop
1011
implicit none
1112
private
1213
public :: basename, canon_path, dirname, is_dir, join_path, number_of_rows, read_lines, list_files, env_variable, &
@@ -306,7 +307,7 @@ subroutine mkdir(dir)
306307
end select
307308

308309
if (stat /= 0) then
309-
stop 'execute_command_line() failed'
310+
call fpm_stop(1, '*mkdir*:directory creation failed')
310311
end if
311312
end subroutine mkdir
312313

@@ -343,7 +344,7 @@ recursive subroutine list_files(dir, files, recurse)
343344
end select
344345

345346
if (stat /= 0) then
346-
stop 'execute_command_line() failed'
347+
call fpm_stop(2,'*list_files*:directory listing failed')
347348
end if
348349

349350
open (newunit=fh, file=temp_file, status='old')
@@ -554,13 +555,11 @@ subroutine fileopen(filename,lun,ier)
554555
ios=0
555556
endif
556557
if(ios.ne.0)then
557-
write(stderr,'(*(a:,1x))')&
558-
& '<ERROR> *filewrite*:',filename,trim(message)
559558
lun=-1
560559
if(present(ier))then
561560
ier=ios
562561
else
563-
stop 1
562+
call fpm_stop(3,'*fileopen*:'//filename//':'//trim(message))
564563
endif
565564
endif
566565

@@ -575,11 +574,10 @@ subroutine fileclose(lun,ier)
575574
if(lun.ne.-1)then
576575
close(unit=lun,iostat=ios,iomsg=message)
577576
if(ios.ne.0)then
578-
write(stderr,'(*(a:,1x))')'<ERROR> *filewrite*:',trim(message)
579577
if(present(ier))then
580578
ier=ios
581579
else
582-
stop 2
580+
call fpm_stop(4,'*fileclose*:'//trim(message))
583581
endif
584582
endif
585583
endif
@@ -599,9 +597,7 @@ subroutine filewrite(filename,filedata)
599597
do i=1,size(filedata)
600598
write(lun,'(a)',iostat=ios,iomsg=message)trim(filedata(i))
601599
if(ios.ne.0)then
602-
write(stderr,'(*(a:,1x))')&
603-
& '<ERROR> *filewrite*:',filename,trim(message)
604-
stop 4
600+
call fpm_stop(5,'*filewrite*:'//filename//':'//trim(message))
605601
endif
606602
enddo
607603
endif

src/fpm_targets.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -341,7 +341,7 @@ end subroutine add_dependency
341341
!>
342342
!> - Executable sources (`FPM_SCOPE_APP`,`FPM_SCOPE_TEST`) may use
343343
!> library modules (including dependencies) as well as any modules
344-
!> corresponding to source files in the same directory or a
344+
!> corresponding to source files in the same directory or a
345345
!> subdirectory of the executable source file.
346346
!>
347347
!> @warning If a module used by a source file cannot be resolved to

0 commit comments

Comments
 (0)