Skip to content

Commit 2ae0581

Browse files
authored
Allow running fpm-new in current directory (#630)
1 parent 64ce7b9 commit 2ae0581

File tree

1 file changed

+20
-5
lines changed

1 file changed

+20
-5
lines changed

src/fpm_command_line.f90

Lines changed: 20 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -31,10 +31,12 @@ module fpm_command_line
3131
use fpm_strings, only : lower, split, fnv_1a, to_fortran_name, is_fortran_name
3232
use fpm_filesystem, only : basename, canon_path, which
3333
use fpm_environment, only : run, get_command_arguments_quoted
34-
use fpm_error, only : fpm_stop
34+
use fpm_os, only : get_current_directory
35+
use fpm_error, only : fpm_stop, error_t
3536
use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, &
3637
& stdout=>output_unit, &
3738
& stderr=>error_unit
39+
3840
implicit none
3941

4042
private
@@ -179,6 +181,7 @@ subroutine get_command_line_settings(cmd_settings)
179181
character(len=*), parameter :: fc_env = "FC", cc_env = "CC", ar_env = "AR", &
180182
& fflags_env = "FFLAGS", cflags_env = "CFLAGS", ldflags_env = "LDFLAGS", &
181183
& fc_default = "gfortran", cc_default = " ", ar_default = " ", flags_default = " "
184+
type(error_t), allocatable :: error
182185

183186
call set_help()
184187
! text for --version switch,
@@ -317,9 +320,13 @@ subroutine get_command_line_settings(cmd_settings)
317320
& help_new, version_text)
318321
select case(size(unnamed))
319322
case(1)
320-
write(stderr,'(*(7x,g0,/))') &
321-
& '<USAGE> fpm new NAME [[--lib|--src] [--app] [--test] [--example]]|[--full|--bare] [--backfill]'
322-
call fpm_stop(1,'directory name required')
323+
if(lget('backfill'))then
324+
name='.'
325+
else
326+
write(stderr,'(*(7x,g0,/))') &
327+
& '<USAGE> fpm new NAME [[--lib|--src] [--app] [--test] [--example]]|[--full|--bare] [--backfill]'
328+
call fpm_stop(1,'directory name required')
329+
endif
323330
case(2)
324331
name=trim(unnamed(2))
325332
case default
@@ -328,6 +335,13 @@ subroutine get_command_line_settings(cmd_settings)
328335
call fpm_stop(2,'only one directory name allowed')
329336
end select
330337
!*! canon_path is not converting ".", etc.
338+
if(name.eq.'.')then
339+
call get_current_directory(name, error)
340+
if (allocated(error)) then
341+
write(stderr, '("[Error]", 1x, a)') error%message
342+
stop 1
343+
endif
344+
endif
331345
name=canon_path(name)
332346
if( .not.is_fortran_name(to_fortran_name(basename(name))) )then
333347
write(stderr,'(g0)') [ character(len=72) :: &
@@ -336,6 +350,7 @@ subroutine get_command_line_settings(cmd_settings)
336350
call fpm_stop(4,' ')
337351
endif
338352

353+
339354
allocate(fpm_new_settings :: cmd_settings)
340355
if (any( specified([character(len=10) :: 'src','lib','app','test','example','bare'])) &
341356
& .and.lget('full') )then
@@ -1079,7 +1094,7 @@ subroutine set_help()
10791094
' fpm new A --full # create example/ and an annotated fpm.toml as well', &
10801095
' fpm new A --bare # create no directories ', &
10811096
' create any missing files in current directory ', &
1082-
' fpm new `pwd` --full --backfill ', &
1097+
' fpm new --full --backfill ', &
10831098
'' ]
10841099
help_test=[character(len=80) :: &
10851100
'NAME ', &

0 commit comments

Comments
 (0)