Skip to content

Commit f884bfd

Browse files
committed
Merge branch 'upstream_master' into file-listing
2 parents 5302799 + 68937a4 commit f884bfd

18 files changed

+216
-199
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-
error 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-
error 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-
error 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-
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

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-
error 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: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -55,9 +55,10 @@ module fpm_cmd_new
5555

5656
use fpm_command_line, only : fpm_new_settings
5757
use fpm_environment, only : run, OS_LINUX, OS_MACOS, OS_WINDOWS
58-
use fpm_filesystem, only : join_path, exists, basename, mkdir, is_dir, to_fortran_name
58+
use fpm_filesystem, only : join_path, exists, basename, mkdir, is_dir
5959
use fpm_filesystem, only : fileopen, fileclose, filewrite, warnwrite
60-
use fpm_strings, only : join
60+
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-
error stop 1
63+
call fpm_stop(1, error%message)
6564
end if
6665
end subroutine handle_error
6766

src/fpm/error.f90

Lines changed: 63 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,15 @@
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
4+
use fpm_strings, only : is_fortran_name, to_fortran_name
35
implicit none
46
private
57

68
public :: error_t
79
public :: fatal_error, syntax_error, file_not_found_error
810
public :: file_parse_error
11+
public :: bad_name_error
12+
public :: fpm_stop
913

1014

1115
!> Data type defining an error
@@ -16,16 +20,8 @@ module fpm_error
1620

1721
end type error_t
1822

19-
20-
!> Alias syntax errors to fatal errors for now
21-
interface syntax_error
22-
module procedure :: fatal_error
23-
end interface syntax_error
24-
25-
2623
contains
2724

28-
2925
!> Generic fatal runtime error
3026
subroutine fatal_error(error, message)
3127

@@ -40,6 +36,43 @@ subroutine fatal_error(error, message)
4036

4137
end subroutine fatal_error
4238

39+
subroutine syntax_error(error, message)
40+
41+
!> Instance of the error data
42+
type(error_t), allocatable, intent(out) :: error
43+
44+
!> Error message
45+
character(len=*), intent(in) :: message
46+
47+
allocate(error)
48+
error%message = message
49+
50+
end subroutine syntax_error
51+
52+
function bad_name_error(error, label,name)
53+
54+
!> Instance of the error data
55+
type(error_t), allocatable, intent(out) :: error
56+
57+
!> Error message label to add to message
58+
character(len=*), intent(in) :: label
59+
60+
!> name value to check
61+
character(len=*), intent(in) :: name
62+
63+
logical :: bad_name_error
64+
65+
if(.not.is_fortran_name(to_fortran_name(name)))then
66+
bad_name_error=.true.
67+
allocate(error)
68+
error%message = 'manifest file syntax error: '//label//' name must be composed only of &
69+
&alphanumerics, "-" and "_" and start with a letter ::'//name
70+
else
71+
bad_name_error=.false.
72+
endif
73+
74+
end function bad_name_error
75+
4376

4477
!> Error created when a file is missing or not found
4578
subroutine file_not_found_error(error, file_name)
@@ -82,9 +115,9 @@ subroutine file_parse_error(error, file_name, message, line_num, &
82115

83116
allocate(error)
84117
error%message = 'Parse error: '//message//new_line('a')
85-
118+
86119
error%message = error%message//file_name
87-
120+
88121
if (present(line_num)) then
89122

90123
write(temp_string,'(I0)') line_num
@@ -115,14 +148,32 @@ subroutine file_parse_error(error, file_name, message, line_num, &
115148

116149
error%message = error%message//new_line('a')
117150
error%message = error%message//' | '//repeat(' ',line_col-1)//'^'
118-
151+
119152
end if
120-
153+
121154
end if
122155

123156
end if
124157

125158
end subroutine file_parse_error
126159

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
127178

128179
end module fpm_error

src/fpm/manifest/example.f90

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@
1717
module fpm_manifest_example
1818
use fpm_manifest_dependency, only : dependency_config_t, new_dependencies
1919
use fpm_manifest_executable, only : executable_config_t
20-
use fpm_error, only : error_t, syntax_error
20+
use fpm_error, only : error_t, syntax_error, bad_name_error
2121
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
2222
implicit none
2323
private
@@ -61,6 +61,9 @@ subroutine new_example(self, table, error)
6161
call syntax_error(error, "Could not retrieve example name")
6262
return
6363
end if
64+
if (bad_name_error(error,'example',self%name))then
65+
return
66+
endif
6467
call get_value(table, "source-dir", self%source_dir, "example")
6568
call get_value(table, "main", self%main, "main.f90")
6669

src/fpm/manifest/executable.f90

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -12,8 +12,8 @@
1212
!>```
1313
module fpm_manifest_executable
1414
use fpm_manifest_dependency, only : dependency_config_t, new_dependencies
15-
use fpm_error, only : error_t, syntax_error
16-
use fpm_strings, only : string_t
15+
use fpm_error, only : error_t, syntax_error, bad_name_error
16+
use fpm_strings, only : string_t
1717
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
1818
implicit none
1919
private
@@ -72,6 +72,9 @@ subroutine new_executable(self, table, error)
7272
call syntax_error(error, "Could not retrieve executable name")
7373
return
7474
end if
75+
if (bad_name_error(error,'executable',self%name))then
76+
return
77+
endif
7578
call get_value(table, "source-dir", self%source_dir, "app")
7679
call get_value(table, "main", self%main, "main.f90")
7780

src/fpm/manifest/package.f90

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -39,7 +39,7 @@ module fpm_manifest_package
3939
use fpm_manifest_install, only: install_config_t, new_install_config
4040
use fpm_manifest_test, only : test_config_t, new_test
4141
use fpm_filesystem, only : exists, getline, join_path
42-
use fpm_error, only : error_t, fatal_error, syntax_error
42+
use fpm_error, only : error_t, fatal_error, syntax_error, bad_name_error
4343
use fpm_toml, only : toml_table, toml_array, toml_key, toml_stat, get_value, &
4444
& len
4545
use fpm_versioning, only : version_t, new_version
@@ -131,6 +131,9 @@ subroutine new_package(self, table, root, error)
131131
call syntax_error(error, "Could not retrieve package name")
132132
return
133133
end if
134+
if (bad_name_error(error,'package',self%name))then
135+
return
136+
endif
134137

135138
if (len(self%name) <= 0) then
136139
call syntax_error(error, "Package name must be a non-empty string")

src/fpm/manifest/test.f90

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@
1717
module fpm_manifest_test
1818
use fpm_manifest_dependency, only : dependency_config_t, new_dependencies
1919
use fpm_manifest_executable, only : executable_config_t
20-
use fpm_error, only : error_t, syntax_error
20+
use fpm_error, only : error_t, syntax_error, bad_name_error
2121
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
2222
implicit none
2323
private
@@ -61,6 +61,9 @@ subroutine new_test(self, table, error)
6161
call syntax_error(error, "Could not retrieve test name")
6262
return
6363
end if
64+
if (bad_name_error(error,'test',self%name))then
65+
return
66+
endif
6467
call get_value(table, "source-dir", self%source_dir, "test")
6568
call get_value(table, "main", self%main, "main.f90")
6669

0 commit comments

Comments
 (0)