Skip to content

Commit bc9fa94

Browse files
committed
rebased
1 parent b3e3d83 commit bc9fa94

File tree

8 files changed

+78
-43
lines changed

8 files changed

+78
-43
lines changed

CONTRIBUTING.md

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -115,7 +115,7 @@ open an issue and we’ll discuss it.
115115

116116
If you have never created a pull request before, welcome :tada:.
117117
You can learn how from
118-
[this great tutorial](https://egghead.io/series/how-to-contribute-to-an-open-source-project-on-github).
118+
[this great tutorial](https://app.egghead.io/courses/how-to-contribute-to-an-open-source-project-on-github).
119119

120120
Don’t know where to start?
121121
You can start by looking through the list of

fpm/src/fpm/cmd/new.f90

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -55,7 +55,7 @@ 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
58+
use fpm_filesystem, only : join_path, exists, basename, mkdir, is_dir, to_fortran_name
5959
use fpm_filesystem, only : fileopen, fileclose, filewrite, warnwrite
6060
use fpm_strings, only : join
6161
use,intrinsic :: iso_fortran_env, only : stderr=>error_unit
@@ -71,7 +71,7 @@ subroutine cmd_new(settings)
7171
character(len=:,kind=tfc),allocatable :: bname ! baeename of NAME
7272
character(len=:,kind=tfc),allocatable :: tomlfile(:)
7373
character(len=:,kind=tfc),allocatable :: littlefile(:)
74-
74+
7575
!> TOP DIRECTORY NAME PROCESSING
7676
!> see if requested new directory already exists and process appropriately
7777
if(exists(settings%name) .and. .not.settings%backfill )then
@@ -310,7 +310,7 @@ subroutine cmd_new(settings)
310310
endif
311311
! create placeholder module src/bname.f90
312312
littlefile=[character(len=80) :: &
313-
&'module '//bname, &
313+
&'module '//to_fortran_name(bname), &
314314
&' implicit none', &
315315
&' private', &
316316
&'', &
@@ -319,7 +319,7 @@ subroutine cmd_new(settings)
319319
&' subroutine say_hello', &
320320
&' print *, "Hello, '//bname//'!"', &
321321
&' end subroutine say_hello', &
322-
&'end module '//bname]
322+
&'end module '//to_fortran_name(bname)]
323323
! create NAME/src/NAME.f90
324324
call warnwrite(join_path(settings%name, 'src', bname//'.f90'),&
325325
& littlefile)
@@ -460,7 +460,7 @@ subroutine cmd_new(settings)
460460
if(exists(bname//'/src/'))then
461461
littlefile=[character(len=80) :: &
462462
&'program main', &
463-
&' use '//bname//', only: say_hello', &
463+
&' use '//to_fortran_name(bname)//', only: say_hello', &
464464
&' implicit none', &
465465
&'', &
466466
&' call say_hello()', &

fpm/src/fpm_command_line.f90

Lines changed: 4 additions & 7 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
@@ -231,13 +231,10 @@ subroutine get_command_line_settings(cmd_settings)
231231
end select
232232
!*! canon_path is not converting ".", etc.
233233
name=canon_path(name)
234-
if( .not.is_fortran_name(basename(name)) )then
234+
if( .not.is_fortran_name(to_fortran_name(basename(name))) )then
235235
write(stderr,'(g0)') [ character(len=72) :: &
236-
& '<ERROR>the new directory basename must be an allowed ', &
237-
& ' Fortran name. It must be composed of 1 to 63 ASCII', &
238-
& ' characters and start with a letter and be composed', &
239-
& ' entirely of alphanumeric characters [a-zA-Z0-9]', &
240-
& ' and underscores.']
236+
& '<ERROR> the fpm project name must be made of up to 63 ASCII letters,', &
237+
& ' numbers, underscores, or hyphens, and start with a letter.']
241238
stop 4
242239
endif
243240

fpm/src/fpm_filesystem.f90

Lines changed: 13 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -3,11 +3,11 @@ module fpm_filesystem
33
use fpm_environment, only: get_os_type, &
44
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
55
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD
6-
use fpm_strings, only: f_string, string_t, split
6+
use fpm_strings, only: f_string, replace, string_t, split
77
implicit none
88
private
99
public :: basename, canon_path, dirname, is_dir, join_path, number_of_rows, read_lines, list_files, env_variable, &
10-
mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file
10+
mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file, to_fortran_name
1111
public :: fileopen, fileclose, filewrite, warnwrite
1212

1313
integer, parameter :: LINE_BUFFER_LEN = 1000
@@ -147,8 +147,6 @@ function dirname(path) result (dir)
147147
character(*), intent(in) :: path
148148
character(:), allocatable :: dir
149149

150-
character(:), allocatable :: file_parts(:)
151-
152150
dir = path(1:scan(path,'/\',back=.true.))
153151

154152
end function dirname
@@ -486,7 +484,7 @@ subroutine fileopen(filename,lun,ier)
486484
character(len=*),intent(in) :: filename
487485
integer,intent(out) :: lun
488486
integer,intent(out),optional :: ier
489-
integer :: i, ios
487+
integer :: ios
490488
character(len=256) :: message
491489

492490
message=' '
@@ -562,4 +560,14 @@ subroutine filewrite(filename,filedata)
562560

563561
end subroutine filewrite
564562

563+
pure function to_fortran_name(string) result(res)
564+
! Returns string with special characters replaced with an underscore.
565+
! For now, only a hyphen is treated as a special character, but this can be
566+
! expanded to other characters if needed.
567+
character(*), intent(in) :: string
568+
character(len(string)) :: res
569+
character, parameter :: SPECIAL_CHARACTERS(*) = ['-']
570+
res = replace(string, SPECIAL_CHARACTERS, '_')
571+
end function to_fortran_name
572+
565573
end module fpm_filesystem

fpm/src/fpm_source_parsing.f90

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@
1616
!>
1717
module fpm_source_parsing
1818
use fpm_error, only: error_t, file_parse_error, fatal_error
19-
use fpm_strings, only: string_t, string_cat, split, lower, str_ends_with, fnv_1a
19+
use fpm_strings, only: string_t, string_cat, len_trim, split, lower, str_ends_with, fnv_1a
2020
use fpm_model, only: srcfile_t, &
2121
FPM_UNIT_UNKNOWN, FPM_UNIT_PROGRAM, FPM_UNIT_MODULE, &
2222
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, &
@@ -476,4 +476,4 @@ function split_n(string,delims,n,stat) result(substring)
476476

477477
end function split_n
478478

479-
end module fpm_source_parsing
479+
end module fpm_source_parsing

fpm/src/fpm_strings.f90

Lines changed: 33 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -4,13 +4,17 @@ module fpm_strings
44

55
private
66
public :: f_string, lower, split, str_ends_with, string_t
7-
public :: string_array_contains, string_cat, operator(.in.), fnv_1a
8-
public :: resize, str, join
7+
public :: string_array_contains, string_cat, len_trim, operator(.in.), fnv_1a
8+
public :: replace, resize, str, join
99

1010
type string_t
1111
character(len=:), allocatable :: s
1212
end type
1313

14+
interface len_trim
15+
module procedure :: string_len_trim
16+
end interface len_trim
17+
1418
interface resize
1519
module procedure :: resize_string
1620
end interface
@@ -177,7 +181,7 @@ function string_cat(strings,delim) result(cat)
177181
character(*), intent(in), optional :: delim
178182
character(:), allocatable :: cat
179183

180-
integer :: i,n
184+
integer :: i
181185
character(:), allocatable :: delim_str
182186

183187
if (size(strings) < 1) then
@@ -200,6 +204,18 @@ function string_cat(strings,delim) result(cat)
200204

201205
end function string_cat
202206

207+
!> Determine total trimmed length of `string_t` array
208+
pure function string_len_trim(strings) result(n)
209+
type(string_t), intent(in) :: strings(:)
210+
integer :: i, n
211+
212+
n = 0
213+
do i=1,size(strings)
214+
n = n + len_trim(strings(i)%s)
215+
end do
216+
217+
end function string_len_trim
218+
203219
subroutine split(input_line,array,delimiters,order,nulls)
204220
! parse string on delimiter characters and store tokens into an allocatable array"
205221
! Author: John S. Urban
@@ -318,6 +334,20 @@ subroutine split(input_line,array,delimiters,order,nulls)
318334
enddo
319335
end subroutine split
320336

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

fpm/test/fpm_test/main.f90

Lines changed: 13 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -14,12 +14,12 @@ program fpm_testing
1414
implicit none
1515
integer :: stat, is
1616
character(len=:), allocatable :: suite_name, test_name
17-
type(testsuite_t), allocatable :: testsuite(:)
17+
type(testsuite_t), allocatable :: suite(:)
1818
character(len=*), parameter :: fmt = '("#", *(1x, a))'
1919

2020
stat = 0
2121

22-
testsuite = [ &
22+
suite = [ &
2323
& new_testsuite("fpm_toml", collect_toml), &
2424
& new_testsuite("fpm_manifest", collect_manifest), &
2525
& new_testsuite("fpm_source_parsing", collect_source_parsing), &
@@ -34,29 +34,29 @@ program fpm_testing
3434
call get_argument(2, test_name)
3535

3636
if (allocated(suite_name)) then
37-
is = select_suite(testsuite, suite_name)
38-
if (is > 0 .and. is <= size(testsuite)) then
37+
is = select_suite(suite, suite_name)
38+
if (is > 0 .and. is <= size(suite)) then
3939
if (allocated(test_name)) then
40-
write(error_unit, fmt) "Suite:", testsuite(is)%name
41-
call run_selected(testsuite(is)%collect, test_name, error_unit, stat)
40+
write(error_unit, fmt) "Suite:", suite(is)%name
41+
call run_selected(suite(is)%collect, test_name, error_unit, stat)
4242
if (stat < 0) then
4343
error stop 1
4444
end if
4545
else
46-
write(error_unit, fmt) "Testing:", testsuite(is)%name
47-
call run_testsuite(testsuite(is)%collect, error_unit, stat)
46+
write(error_unit, fmt) "Testing:", suite(is)%name
47+
call run_testsuite(suite(is)%collect, error_unit, stat)
4848
end if
4949
else
5050
write(error_unit, fmt) "Available testsuites"
51-
do is = 1, size(testsuite)
52-
write(error_unit, fmt) "-", testsuite(is)%name
51+
do is = 1, size(suite)
52+
write(error_unit, fmt) "-", suite(is)%name
5353
end do
5454
error stop 1
5555
end if
5656
else
57-
do is = 1, size(testsuite)
58-
write(error_unit, fmt) "Testing:", testsuite(is)%name
59-
call run_testsuite(testsuite(is)%collect, error_unit, stat)
57+
do is = 1, size(suite)
58+
write(error_unit, fmt) "Testing:", suite(is)%name
59+
call run_testsuite(suite(is)%collect, error_unit, stat)
6060
end do
6161
end if
6262

fpm/test/new_test/new_test.f90

Lines changed: 7 additions & 7 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', &
@@ -64,7 +64,7 @@ program new_test
6464
if( is_dir(trim(directories(i))) ) then
6565
write(*,*)'ERROR:',trim( directories(i) ),' already exists'
6666
write(*,*)' you must remove scratch directories before performing this test'
67-
write(*,'(*(g0:,1x))')'directories:',(trim(directories(j)),j=1,size(directories)),'no-no'
67+
write(*,'(*(g0:,1x))')'directories:',(trim(directories(j)),j=1,size(directories)),'name-with-hyphens'
6868
stop
6969
endif
7070
enddo
@@ -76,12 +76,12 @@ program new_test
7676
write(*,'(*(g0))')'CMD=',trim(cmds(i)),' EXITSTAT=',estat,' CMDSTAT=',cstat,' MESSAGE=',trim(message)
7777
enddo
7878

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

8686
! assuming hidden files in .git and .gitignore are ignored for now
8787
TESTS: do i=1,size(directories)

0 commit comments

Comments
 (0)