Skip to content

Commit c485357

Browse files
authored
Merge pull request #337 from milancurcic/allow-hyphen-in-fpm-names
Allow hyphens in fpm project names in "fpm new"
2 parents cf49f39 + 838ba4c commit c485357

File tree

5 files changed

+44
-23
lines changed

5 files changed

+44
-23
lines changed

fpm/src/fpm/cmd/new.f90

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,7 @@ module fpm_cmd_new
22

33
use fpm_command_line, only : fpm_new_settings
44
use fpm_environment, only : run, OS_LINUX, OS_MACOS, OS_WINDOWS
5-
use fpm_filesystem, only : join_path, exists, basename, mkdir, is_dir
5+
use fpm_filesystem, only : join_path, exists, basename, mkdir, is_dir, to_fortran_name
66
use,intrinsic :: iso_fortran_env, only : stderr=>error_unit
77
implicit none
88
private
@@ -70,7 +70,7 @@ subroutine cmd_new(settings)
7070
&'']
7171
! create placeholder module src/bname.f90
7272
littlefile=[character(len=80) :: &
73-
&'module '//bname, &
73+
&'module '//to_fortran_name(bname), &
7474
&' implicit none', &
7575
&' private', &
7676
&'', &
@@ -79,7 +79,7 @@ subroutine cmd_new(settings)
7979
&' subroutine say_hello', &
8080
&' print *, "Hello, '//bname//'!"', &
8181
&' end subroutine say_hello', &
82-
&'end module '//bname]
82+
&'end module '//to_fortran_name(bname)]
8383
! create NAME/src/NAME.f90
8484
call warnwrite(join_path(settings%name, 'src', bname//'.f90'),&
8585
& littlefile)
@@ -121,7 +121,7 @@ subroutine cmd_new(settings)
121121
if(exists(bname//'/src/'))then
122122
littlefile=[character(len=80) :: &
123123
&'program main', &
124-
&' use '//bname//', only: say_hello', &
124+
&' use '//to_fortran_name(bname)//', only: say_hello', &
125125
&' implicit none', &
126126
&'', &
127127
&' call say_hello()', &

fpm/src/fpm_command_line.f90

Lines changed: 6 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ module fpm_command_line
2828
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD
2929
use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified
3030
use fpm_strings, only : lower, split
31-
use fpm_filesystem, only : basename, canon_path
31+
use fpm_filesystem, only : basename, canon_path, to_fortran_name
3232
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
3333
& stdout=>output_unit, &
3434
& stderr=>error_unit
@@ -225,13 +225,10 @@ subroutine get_command_line_settings(cmd_settings)
225225
end select
226226
!*! canon_path is not converting ".", etc.
227227
name=canon_path(name)
228-
if( .not.is_fortran_name(basename(name)) )then
228+
if( .not.is_fortran_name(to_fortran_name(basename(name))) )then
229229
write(stderr,'(g0)') [ character(len=72) :: &
230-
& '<ERROR>the new directory basename must be an allowed ', &
231-
& ' Fortran name. It must be composed of 1 to 63 ASCII', &
232-
& ' characters and start with a letter and be composed', &
233-
& ' entirely of alphanumeric characters [a-zA-Z0-9]', &
234-
& ' and underscores.']
230+
& '<ERROR> the fpm project name must be made of up to 63 ASCII letters,', &
231+
& ' numbers, underscores, or hyphens, and start with a letter.']
235232
stop 4
236233
endif
237234

@@ -823,9 +820,8 @@ subroutine set_help()
823820
' ', &
824821
'OPTIONS ', &
825822
' NAME the name of the project directory to create. The name ', &
826-
' must be a valid Fortran name composed of 1 to 63 ', &
827-
' ASCII alphanumeric characters and underscores, ', &
828-
' starting with a letter. ', &
823+
' must be made of up to 63 ASCII letters, digits, underscores, ', &
824+
' or hyphens, and start with a letter. ', &
829825
' ', &
830826
' The default is to create all of the src/, app/, and test/ ', &
831827
' directories. If any of the following options are specified ', &

fpm/src/fpm_filesystem.f90

Lines changed: 13 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,11 +2,11 @@ module fpm_filesystem
22
use fpm_environment, only: get_os_type, &
33
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
44
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD
5-
use fpm_strings, only: f_string, string_t, split
5+
use fpm_strings, only: f_string, replace, string_t, split
66
implicit none
77
private
88
public :: basename, canon_path, dirname, is_dir, join_path, number_of_rows, read_lines, list_files, env_variable, &
9-
mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file
9+
mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file, to_fortran_name
1010

1111
integer, parameter :: LINE_BUFFER_LEN = 1000
1212

@@ -465,4 +465,15 @@ subroutine delete_file(file)
465465
end subroutine delete_file
466466

467467

468+
pure function to_fortran_name(string) result(res)
469+
! Returns string with special characters replaced with an underscore.
470+
! For now, only a hyphen is treated as a special character, but this can be
471+
! expanded to other characters if needed.
472+
character(*), intent(in) :: string
473+
character(len(string)) :: res
474+
character, parameter :: SPECIAL_CHARACTERS(*) = ['-']
475+
res = replace(string, SPECIAL_CHARACTERS, '_')
476+
end function to_fortran_name
477+
478+
468479
end module fpm_filesystem

fpm/src/fpm_strings.f90

Lines changed: 15 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ module fpm_strings
55
private
66
public :: f_string, lower, split, str_ends_with, string_t
77
public :: string_array_contains, string_cat, len_trim, operator(.in.), fnv_1a
8-
public :: resize, str
8+
public :: replace, resize, str
99

1010
type string_t
1111
character(len=:), allocatable :: s
@@ -335,6 +335,20 @@ subroutine split(input_line,array,delimiters,order,nulls)
335335
enddo
336336
end subroutine split
337337

338+
pure function replace(string, charset, target_char) result(res)
339+
! Returns string with characters in charset replaced with target_char.
340+
character(*), intent(in) :: string
341+
character, intent(in) :: charset(:), target_char
342+
character(len(string)) :: res
343+
integer :: n
344+
res = string
345+
do n = 1, len(string)
346+
if (any(string(n:n) == charset)) then
347+
res(n:n) = target_char
348+
end if
349+
end do
350+
end function replace
351+
338352
subroutine resize_string(list, n)
339353
!> Instance of the array to be resized
340354
type(string_t), allocatable, intent(inout) :: list(:)

fpm/test/new_test/new_test.f90

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@ program new_test
1313
character(len=*),parameter :: cmds(*) = [character(len=80) :: &
1414
! run a variety of "fpm new" variations and verify expected files are generated
1515
' new', &
16-
' new no-no', &
16+
' new name-with-hyphens', &
1717
' new '//scr//'A', &
1818
' new '//scr//'B --lib', &
1919
' new '//scr//'C --app', &
@@ -63,7 +63,7 @@ program new_test
6363
if( is_dir(trim(directories(i))) ) then
6464
write(*,*)'ERROR:',trim( directories(i) ),' already exists'
6565
write(*,*)' you must remove scratch directories before performing this test'
66-
write(*,'(*(g0:,1x))')'directories:',(trim(directories(j)),j=1,size(directories)),'no-no'
66+
write(*,'(*(g0:,1x))')'directories:',(trim(directories(j)),j=1,size(directories)),'name-with-hyphens'
6767
stop
6868
endif
6969
enddo
@@ -75,11 +75,11 @@ program new_test
7575
write(*,'(*(g0))')'CMD=',trim(cmds(i)),' EXITSTAT=',estat,' CMDSTAT=',cstat,' MESSAGE=',trim(message)
7676
enddo
7777

78-
if( is_dir('no-no') ) then
79-
tally=[tally,.false.]
80-
write(*,*)'ERROR: directory no-no/ exists'
81-
else
78+
if( is_dir('name-with-hyphens') ) then
8279
tally=[tally,.true.]
80+
else
81+
write(*,*)'ERROR: directory name-with-hyphens/ exists'
82+
tally=[tally,.false.]
8383
endif
8484

8585
! assuming hidden files in .git and .gitignore are ignored for now

0 commit comments

Comments
 (0)