Skip to content

Commit 9aae783

Browse files
committed
check name used for package, executable, test, or example
1 parent 5617e65 commit 9aae783

14 files changed

+92
-101
lines changed

src/fpm.f90

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -256,19 +256,19 @@ subroutine cmd_build(settings)
256256
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
257257
if (allocated(error)) then
258258
print '(a)', error%message
259-
error stop 1
259+
stop 1
260260
end if
261261

262262
call build_model(model, settings, package, error)
263263
if (allocated(error)) then
264264
print '(a)', error%message
265-
error stop 1
265+
stop 1
266266
end if
267267

268268
call targets_from_sources(targets,model,error)
269269
if (allocated(error)) then
270270
print '(a)', error%message
271-
error stop 1
271+
stop 1
272272
end if
273273

274274
if(settings%list)then
@@ -305,19 +305,19 @@ subroutine cmd_run(settings,test)
305305
call get_package_data(package, "fpm.toml", error, apply_defaults=.true.)
306306
if (allocated(error)) then
307307
print '(a)', error%message
308-
error stop 1
308+
stop 1
309309
end if
310310

311311
call build_model(model, settings%fpm_build_settings, package, error)
312312
if (allocated(error)) then
313313
print '(a)', error%message
314-
error stop 1
314+
stop 1
315315
end if
316316

317317
call targets_from_sources(targets,model,error)
318318
if (allocated(error)) then
319319
print '(a)', error%message
320-
error stop 1
320+
stop 1
321321
end if
322322

323323
if (test) then

src/fpm/cmd/install.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -169,7 +169,7 @@ subroutine handle_error(error)
169169
type(error_t), intent(in), optional :: error
170170
if (present(error)) then
171171
print '("[Error]", 1x, a)', error%message
172-
error stop 1
172+
stop 1
173173
end if
174174
end subroutine handle_error
175175

src/fpm/cmd/new.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -55,9 +55,9 @@ 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
6161
use,intrinsic :: iso_fortran_env, only : stderr=>error_unit
6262
implicit none
6363
private

src/fpm/cmd/update.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -61,7 +61,7 @@ subroutine handle_error(error)
6161
type(error_t), intent(in), optional :: error
6262
if (present(error)) then
6363
print '(a)', error%message
64-
error stop 1
64+
stop 1
6565
end if
6666
end subroutine handle_error
6767

src/fpm/error.f90

Lines changed: 13 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -16,16 +16,8 @@ module fpm_error
1616

1717
end type error_t
1818

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-
2619
contains
2720

28-
2921
!> Generic fatal runtime error
3022
subroutine fatal_error(error, message)
3123

@@ -40,6 +32,19 @@ subroutine fatal_error(error, message)
4032

4133
end subroutine fatal_error
4234

35+
subroutine syntax_error(error, message)
36+
37+
!> Instance of the error data
38+
type(error_t), allocatable, intent(out) :: error
39+
40+
!> Error message
41+
character(len=*), intent(in) :: message
42+
43+
allocate(error)
44+
error%message = message
45+
46+
end subroutine syntax_error
47+
4348

4449
!> Error created when a file is missing or not found
4550
subroutine file_not_found_error(error, file_name)

src/fpm/manifest/example.f90

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@ module fpm_manifest_example
1919
use fpm_manifest_executable, only : executable_config_t
2020
use fpm_error, only : error_t, syntax_error
2121
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
22+
use fpm_strings, only : to_fortran_name, is_fortran_name
2223
implicit none
2324
private
2425

@@ -61,6 +62,11 @@ subroutine new_example(self, table, error)
6162
call syntax_error(error, "Could not retrieve example name")
6263
return
6364
end if
65+
if(.not.is_fortran_name(to_fortran_name(self%name)))then
66+
call syntax_error(error, 'manifest file syntax error: example name must be composed only of &
67+
&alphanumerics, "-" and "_" and start with a letter')
68+
return
69+
endif
6470
call get_value(table, "source-dir", self%source_dir, "example")
6571
call get_value(table, "main", self%main, "main.f90")
6672

src/fpm/manifest/executable.f90

Lines changed: 6 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@
1313
module fpm_manifest_executable
1414
use fpm_manifest_dependency, only : dependency_config_t, new_dependencies
1515
use fpm_error, only : error_t, syntax_error
16-
use fpm_strings, only : string_t
16+
use fpm_strings, only : string_t, is_fortran_name, to_fortran_name
1717
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
1818
implicit none
1919
private
@@ -72,6 +72,11 @@ subroutine new_executable(self, table, error)
7272
call syntax_error(error, "Could not retrieve executable name")
7373
return
7474
end if
75+
if(.not.is_fortran_name(to_fortran_name(self%name)))then
76+
call syntax_error(error, 'manifest file syntax error: executable name must be composed only of &
77+
&alphanumerics, "-" and "_" and start with a letter')
78+
return
79+
endif
7580
call get_value(table, "source-dir", self%source_dir, "app")
7681
call get_value(table, "main", self%main, "main.f90")
7782

src/fpm/manifest/package.f90

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -42,6 +42,7 @@ module fpm_manifest_package
4242
use fpm_error, only : error_t, fatal_error, syntax_error
4343
use fpm_toml, only : toml_table, toml_array, toml_key, toml_stat, get_value, &
4444
& len
45+
use fpm_strings, only : is_fortran_name, to_fortran_name
4546
use fpm_versioning, only : version_t, new_version
4647
implicit none
4748
private
@@ -131,6 +132,11 @@ subroutine new_package(self, table, root, error)
131132
call syntax_error(error, "Could not retrieve package name")
132133
return
133134
end if
135+
if(.not.is_fortran_name(to_fortran_name(self%name)))then
136+
call syntax_error(error, 'manifest file syntax error: package name must be composed only of &
137+
&alphanumerics, "-" and "_" and start with a letter')
138+
return
139+
endif
134140

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

src/fpm/manifest/test.f90

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@ module fpm_manifest_test
1919
use fpm_manifest_executable, only : executable_config_t
2020
use fpm_error, only : error_t, syntax_error
2121
use fpm_toml, only : toml_table, toml_key, toml_stat, get_value
22+
use fpm_strings, only : to_fortran_name, is_fortran_name
2223
implicit none
2324
private
2425

@@ -61,6 +62,11 @@ subroutine new_test(self, table, error)
6162
call syntax_error(error, "Could not retrieve test name")
6263
return
6364
end if
65+
if(.not.is_fortran_name(to_fortran_name(self%name)))then
66+
call syntax_error(error, 'manifest file syntax error: test name must be composed only of &
67+
&alphanumerics, "-" and "_" and start with a letter')
68+
return
69+
endif
6470
call get_value(table, "source-dir", self%source_dir, "test")
6571
call get_value(table, "main", self%main, "main.f90")
6672

src/fpm_command_line.f90

Lines changed: 2 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -28,8 +28,8 @@ module fpm_command_line
2828
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
2929
use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified
3030
use M_CLI2, only : get_subcommand, CLI_RESPONSE_FILE
31-
use fpm_strings, only : lower, split, fnv_1a
32-
use fpm_filesystem, only : basename, canon_path, to_fortran_name, which
31+
use fpm_strings, only : lower, split, fnv_1a, to_fortran_name, is_fortran_name
32+
use fpm_filesystem, only : basename, canon_path, which
3333
use fpm_environment, only : run, get_command_arguments_quoted
3434
use fpm_compiler, only : get_default_compile_flags
3535
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
@@ -517,27 +517,6 @@ end subroutine printhelp
517517

518518
end subroutine get_command_line_settings
519519

520-
function is_fortran_name(line) result (lout)
521-
! determine if a string is a valid Fortran name ignoring trailing spaces
522-
! (but not leading spaces)
523-
character(len=*),parameter :: int='0123456789'
524-
character(len=*),parameter :: lower='abcdefghijklmnopqrstuvwxyz'
525-
character(len=*),parameter :: upper='ABCDEFGHIJKLMNOPQRSTUVWXYZ'
526-
character(len=*),parameter :: allowed=upper//lower//int//'_'
527-
character(len=*),intent(in) :: line
528-
character(len=:),allocatable :: name
529-
logical :: lout
530-
name=trim(line)
531-
if(len(name).ne.0)then
532-
lout = .true. &
533-
& .and. verify(name(1:1), lower//upper) == 0 &
534-
& .and. verify(name,allowed) == 0 &
535-
& .and. len(name) <= 63
536-
else
537-
lout = .false.
538-
endif
539-
end function is_fortran_name
540-
541520
subroutine set_help()
542521
help_list_nodash=[character(len=80) :: &
543522
'USAGE: fpm [ SUBCOMMAND [SUBCOMMAND_OPTIONS] ]|[--list|--help|--version]', &

0 commit comments

Comments
 (0)