@@ -28,8 +28,8 @@ module fpm_command_line
2828 OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
2929use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified
3030use 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
3333use fpm_environment, only : run, get_command_arguments_quoted
3434use fpm_compiler, only : get_default_compile_flags
3535use ,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