aboutsummaryrefslogtreecommitdiff
path: root/src/fpm_command_line.f90
diff options
context:
space:
mode:
authorLKedward <laurence.kedward@bristol.ac.uk>2021-07-16 15:24:25 +0100
committerLKedward <laurence.kedward@bristol.ac.uk>2021-07-16 15:24:25 +0100
commitf884bfd38a546dba12ccabcce8581e7bab29e51f (patch)
tree9c0f3822b59741f18cfb8feef02db7d27caf712d /src/fpm_command_line.f90
parent53027990c205eb905ff534544f4752ea92e747d7 (diff)
parent68937a4eae6a71b74edbf762c574cc2dc22bb2d6 (diff)
downloadfpm-f884bfd38a546dba12ccabcce8581e7bab29e51f.tar.gz
fpm-f884bfd38a546dba12ccabcce8581e7bab29e51f.zip
Merge branch 'upstream_master' into file-listing
Diffstat (limited to 'src/fpm_command_line.f90')
-rw-r--r--src/fpm_command_line.f9042
1 files changed, 10 insertions, 32 deletions
diff --git a/src/fpm_command_line.f90 b/src/fpm_command_line.f90
index b130f89..2ed7ac6 100644
--- a/src/fpm_command_line.f90
+++ b/src/fpm_command_line.f90
@@ -28,10 +28,11 @@ use fpm_environment, only : get_os_type, get_env, &
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified
use M_CLI2, only : get_subcommand, CLI_RESPONSE_FILE
-use fpm_strings, only : lower, split, fnv_1a
-use fpm_filesystem, only : basename, canon_path, to_fortran_name, which
+use fpm_strings, only : lower, split, fnv_1a, to_fortran_name, is_fortran_name
+use fpm_filesystem, only : basename, canon_path, which
use fpm_environment, only : run, get_command_arguments_quoted
-use fpm_compiler, only : get_default_compile_flags
+use fpm_compiler, only : get_default_compile_flags
+use fpm_error, only : fpm_stop
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
& stdout=>output_unit, &
& stderr=>error_unit
@@ -138,7 +139,7 @@ contains
case default ; os_type = "OS Type: UNKNOWN"
end select
version_text = [character(len=80) :: &
- & 'Version: 0.3.0, alpha', &
+ & 'Version: 0.3.0, alpha', &
& 'Program: fpm(1)', &
& 'Description: A Fortran package manager and build system', &
& 'Home Page: https://github.com/fortran-lang/fpm', &
@@ -244,17 +245,15 @@ contains
& help_new, version_text)
select case(size(unnamed))
case(1)
- write(stderr,'(*(g0,/))')'<ERROR> directory name required'
write(stderr,'(*(7x,g0,/))') &
& '<USAGE> fpm new NAME [[--lib|--src] [--app] [--test] [--example]]|[--full|--bare] [--backfill]'
- stop 1
+ call fpm_stop(1,'directory name required')
case(2)
name=trim(unnamed(2))
case default
- write(stderr,'(g0)')'<ERROR> only one directory name allowed'
write(stderr,'(7x,g0)') &
& '<USAGE> fpm new NAME [[--lib|--src] [--app] [--test] [--example]]| [--full|--bare] [--backfill]'
- stop 2
+ call fpm_stop(2,'only one directory name allowed')
end select
!*! canon_path is not converting ".", etc.
name=canon_path(name)
@@ -262,7 +261,7 @@ contains
write(stderr,'(g0)') [ character(len=72) :: &
& '<ERROR> the fpm project name must be made of up to 63 ASCII letters,', &
& ' numbers, underscores, or hyphens, and start with a letter.']
- stop 4
+ call fpm_stop(4,' ')
endif
allocate(fpm_new_settings :: cmd_settings)
@@ -271,13 +270,13 @@ contains
write(stderr,'(*(a))')&
&'<ERROR> --full and any of [--src|--lib,--app,--test,--example,--bare]', &
&' are mutually exclusive.'
- stop 5
+ call fpm_stop(5,' ')
elseif (any( specified([character(len=10) :: 'src','lib','app','test','example','full'])) &
& .and.lget('bare') )then
write(stderr,'(*(a))')&
&'<ERROR> --bare and any of [--src|--lib,--app,--test,--example,--full]', &
&' are mutually exclusive.'
- stop 3
+ call fpm_stop(3,' ')
elseif (any( specified([character(len=10) :: 'src','lib','app','test','example']) ) )then
cmd_settings=fpm_new_settings(&
& backfill=lget('backfill'), &
@@ -517,27 +516,6 @@ contains
end subroutine get_command_line_settings
- function is_fortran_name(line) result (lout)
- ! determine if a string is a valid Fortran name ignoring trailing spaces
- ! (but not leading spaces)
- character(len=*),parameter :: int='0123456789'
- character(len=*),parameter :: lower='abcdefghijklmnopqrstuvwxyz'
- character(len=*),parameter :: upper='ABCDEFGHIJKLMNOPQRSTUVWXYZ'
- character(len=*),parameter :: allowed=upper//lower//int//'_'
- character(len=*),intent(in) :: line
- character(len=:),allocatable :: name
- logical :: lout
- name=trim(line)
- if(len(name).ne.0)then
- lout = .true. &
- & .and. verify(name(1:1), lower//upper) == 0 &
- & .and. verify(name,allowed) == 0 &
- & .and. len(name) <= 63
- else
- lout = .false.
- endif
- end function is_fortran_name
-
subroutine set_help()
help_list_nodash=[character(len=80) :: &
'USAGE: fpm [ SUBCOMMAND [SUBCOMMAND_OPTIONS] ]|[--list|--help|--version]', &