aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--fpm/src/fpm/cmd/new.f908
-rw-r--r--fpm/src/fpm_command_line.f9016
-rw-r--r--fpm/src/fpm_filesystem.f9015
-rw-r--r--fpm/src/fpm_strings.f9016
-rw-r--r--fpm/test/new_test/new_test.f9012
5 files changed, 44 insertions, 23 deletions
diff --git a/fpm/src/fpm/cmd/new.f90 b/fpm/src/fpm/cmd/new.f90
index 04cd7d5..9f2aa4b 100644
--- a/fpm/src/fpm/cmd/new.f90
+++ b/fpm/src/fpm/cmd/new.f90
@@ -2,7 +2,7 @@ module fpm_cmd_new
use fpm_command_line, only : fpm_new_settings
use fpm_environment, only : run, OS_LINUX, OS_MACOS, OS_WINDOWS
-use fpm_filesystem, only : join_path, exists, basename, mkdir, is_dir
+use fpm_filesystem, only : join_path, exists, basename, mkdir, is_dir, to_fortran_name
use,intrinsic :: iso_fortran_env, only : stderr=>error_unit
implicit none
private
@@ -70,7 +70,7 @@ character(len=8) :: date
&'']
! create placeholder module src/bname.f90
littlefile=[character(len=80) :: &
- &'module '//bname, &
+ &'module '//to_fortran_name(bname), &
&' implicit none', &
&' private', &
&'', &
@@ -79,7 +79,7 @@ character(len=8) :: date
&' subroutine say_hello', &
&' print *, "Hello, '//bname//'!"', &
&' end subroutine say_hello', &
- &'end module '//bname]
+ &'end module '//to_fortran_name(bname)]
! create NAME/src/NAME.f90
call warnwrite(join_path(settings%name, 'src', bname//'.f90'),&
& littlefile)
@@ -121,7 +121,7 @@ character(len=8) :: date
if(exists(bname//'/src/'))then
littlefile=[character(len=80) :: &
&'program main', &
- &' use '//bname//', only: say_hello', &
+ &' use '//to_fortran_name(bname)//', only: say_hello', &
&' implicit none', &
&'', &
&' call say_hello()', &
diff --git a/fpm/src/fpm_command_line.f90 b/fpm/src/fpm_command_line.f90
index f7cd38f..b7b5c2e 100644
--- a/fpm/src/fpm_command_line.f90
+++ b/fpm/src/fpm_command_line.f90
@@ -28,7 +28,7 @@ use fpm_environment, only : get_os_type, get_env, &
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD
use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified
use fpm_strings, only : lower, split
-use fpm_filesystem, only : basename, canon_path
+use fpm_filesystem, only : basename, canon_path, to_fortran_name
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
& stdout=>output_unit, &
& stderr=>error_unit
@@ -225,13 +225,10 @@ contains
end select
!*! canon_path is not converting ".", etc.
name=canon_path(name)
- if( .not.is_fortran_name(basename(name)) )then
+ if( .not.is_fortran_name(to_fortran_name(basename(name))) )then
write(stderr,'(g0)') [ character(len=72) :: &
- & '<ERROR>the new directory basename must be an allowed ', &
- & ' Fortran name. It must be composed of 1 to 63 ASCII', &
- & ' characters and start with a letter and be composed', &
- & ' entirely of alphanumeric characters [a-zA-Z0-9]', &
- & ' and underscores.']
+ & '<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
endif
@@ -823,9 +820,8 @@ contains
' ', &
'OPTIONS ', &
' NAME the name of the project directory to create. The name ', &
- ' must be a valid Fortran name composed of 1 to 63 ', &
- ' ASCII alphanumeric characters and underscores, ', &
- ' starting with a letter. ', &
+ ' must be made of up to 63 ASCII letters, digits, underscores, ', &
+ ' or hyphens, and start with a letter. ', &
' ', &
' The default is to create all of the src/, app/, and test/ ', &
' directories. If any of the following options are specified ', &
diff --git a/fpm/src/fpm_filesystem.f90 b/fpm/src/fpm_filesystem.f90
index f221917..7ed99dc 100644
--- a/fpm/src/fpm_filesystem.f90
+++ b/fpm/src/fpm_filesystem.f90
@@ -2,11 +2,11 @@ module fpm_filesystem
use fpm_environment, only: get_os_type, &
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD
- use fpm_strings, only: f_string, string_t, split
+ use fpm_strings, only: f_string, replace, string_t, split
implicit none
private
public :: basename, canon_path, dirname, is_dir, join_path, number_of_rows, read_lines, list_files, env_variable, &
- mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file
+ mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file, to_fortran_name
integer, parameter :: LINE_BUFFER_LEN = 1000
@@ -465,4 +465,15 @@ subroutine delete_file(file)
end subroutine delete_file
+pure function to_fortran_name(string) result(res)
+ ! Returns string with special characters replaced with an underscore.
+ ! For now, only a hyphen is treated as a special character, but this can be
+ ! expanded to other characters if needed.
+ character(*), intent(in) :: string
+ character(len(string)) :: res
+ character, parameter :: SPECIAL_CHARACTERS(*) = ['-']
+ res = replace(string, SPECIAL_CHARACTERS, '_')
+end function to_fortran_name
+
+
end module fpm_filesystem
diff --git a/fpm/src/fpm_strings.f90 b/fpm/src/fpm_strings.f90
index e3cee28..7d42d22 100644
--- a/fpm/src/fpm_strings.f90
+++ b/fpm/src/fpm_strings.f90
@@ -5,7 +5,7 @@ implicit none
private
public :: f_string, lower, split, str_ends_with, string_t
public :: string_array_contains, string_cat, len_trim, operator(.in.), fnv_1a
-public :: resize, str
+public :: replace, resize, str
type string_t
character(len=:), allocatable :: s
@@ -335,6 +335,20 @@ subroutine split(input_line,array,delimiters,order,nulls)
enddo
end subroutine split
+pure function replace(string, charset, target_char) result(res)
+ ! Returns string with characters in charset replaced with target_char.
+ character(*), intent(in) :: string
+ character, intent(in) :: charset(:), target_char
+ character(len(string)) :: res
+ integer :: n
+ res = string
+ do n = 1, len(string)
+ if (any(string(n:n) == charset)) then
+ res(n:n) = target_char
+ end if
+ end do
+end function replace
+
subroutine resize_string(list, n)
!> Instance of the array to be resized
type(string_t), allocatable, intent(inout) :: list(:)
diff --git a/fpm/test/new_test/new_test.f90 b/fpm/test/new_test/new_test.f90
index 2220b43..0637f0a 100644
--- a/fpm/test/new_test/new_test.f90
+++ b/fpm/test/new_test/new_test.f90
@@ -13,7 +13,7 @@ character(len=*),parameter :: scr = 'fpm_scratch_'
character(len=*),parameter :: cmds(*) = [character(len=80) :: &
! run a variety of "fpm new" variations and verify expected files are generated
' new', &
-' new no-no', &
+' new name-with-hyphens', &
' new '//scr//'A', &
' new '//scr//'B --lib', &
' new '//scr//'C --app', &
@@ -63,7 +63,7 @@ logical :: IS_OS_WINDOWS
if( is_dir(trim(directories(i))) ) then
write(*,*)'ERROR:',trim( directories(i) ),' already exists'
write(*,*)' you must remove scratch directories before performing this test'
- write(*,'(*(g0:,1x))')'directories:',(trim(directories(j)),j=1,size(directories)),'no-no'
+ write(*,'(*(g0:,1x))')'directories:',(trim(directories(j)),j=1,size(directories)),'name-with-hyphens'
stop
endif
enddo
@@ -75,11 +75,11 @@ logical :: IS_OS_WINDOWS
write(*,'(*(g0))')'CMD=',trim(cmds(i)),' EXITSTAT=',estat,' CMDSTAT=',cstat,' MESSAGE=',trim(message)
enddo
- if( is_dir('no-no') ) then
- tally=[tally,.false.]
- write(*,*)'ERROR: directory no-no/ exists'
- else
+ if( is_dir('name-with-hyphens') ) then
tally=[tally,.true.]
+ else
+ write(*,*)'ERROR: directory name-with-hyphens/ exists'
+ tally=[tally,.false.]
endif
! assuming hidden files in .git and .gitignore are ignored for now