Skip to content

Commit 845217f

Browse files
authored
Merge pull request #483 from awvwgk/working-directory
Allow fpm to change the working directory
2 parents e0e6afe + f6eed99 commit 845217f

File tree

5 files changed

+218
-15
lines changed

5 files changed

+218
-15
lines changed

app/main.f90

Lines changed: 77 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
program main
2+
use, intrinsic :: iso_fortran_env, only : error_unit, output_unit
23
use fpm_command_line, only: &
34
fpm_cmd_settings, &
45
fpm_new_settings, &
@@ -8,17 +9,57 @@ program main
89
fpm_install_settings, &
910
fpm_update_settings, &
1011
get_command_line_settings
12+
use fpm_error, only: error_t
13+
use fpm_filesystem, only: exists, parent_dir, join_path
1114
use fpm, only: cmd_build, cmd_run
1215
use fpm_cmd_install, only: cmd_install
1316
use fpm_cmd_new, only: cmd_new
1417
use fpm_cmd_update, only : cmd_update
18+
use fpm_os, only: change_directory, get_current_directory
1519

1620
implicit none
1721

1822
class(fpm_cmd_settings), allocatable :: cmd_settings
23+
type(error_t), allocatable :: error
24+
character(len=:), allocatable :: pwd_start, pwd_working, working_dir, project_root
1925

2026
call get_command_line_settings(cmd_settings)
2127

28+
call get_current_directory(pwd_start, error)
29+
call handle_error(error)
30+
31+
call get_working_dir(cmd_settings, working_dir)
32+
if (allocated(working_dir)) then
33+
! Change working directory if requested
34+
if (len_trim(working_dir) > 0) then
35+
call change_directory(working_dir, error)
36+
call handle_error(error)
37+
38+
call get_current_directory(pwd_working, error)
39+
call handle_error(error)
40+
write(output_unit, '(*(a))') "fpm: Entering directory '"//pwd_working//"'"
41+
else
42+
pwd_working = pwd_start
43+
end if
44+
else
45+
pwd_working = pwd_start
46+
end if
47+
48+
if (.not.has_manifest(pwd_working)) then
49+
project_root = pwd_working
50+
do while(.not.has_manifest(project_root))
51+
working_dir = parent_dir(project_root)
52+
if (len(working_dir) == 0) exit
53+
project_root = working_dir
54+
end do
55+
56+
if (has_manifest(project_root)) then
57+
call change_directory(project_root, error)
58+
call handle_error(error)
59+
write(output_unit, '(*(a))') "fpm: Entering directory '"//project_root//"'"
60+
end if
61+
end if
62+
2263
select type(settings=>cmd_settings)
2364
type is (fpm_new_settings)
2465
call cmd_new(settings)
@@ -34,4 +75,40 @@ program main
3475
call cmd_update(settings)
3576
end select
3677

78+
if (allocated(project_root)) then
79+
write(output_unit, '(*(a))') "fpm: Leaving directory '"//project_root//"'"
80+
end if
81+
82+
if (pwd_start /= pwd_working) then
83+
write(output_unit, '(*(a))') "fpm: Leaving directory '"//pwd_working//"'"
84+
end if
85+
86+
contains
87+
88+
function has_manifest(dir)
89+
character(len=*), intent(in) :: dir
90+
logical :: has_manifest
91+
92+
character(len=:), allocatable :: manifest
93+
94+
has_manifest = exists(join_path(dir, "fpm.toml"))
95+
end function has_manifest
96+
97+
subroutine handle_error(error)
98+
type(error_t), optional, intent(in) :: error
99+
if (present(error)) then
100+
write(error_unit, '("[Error]", 1x, a)') error%message
101+
stop 1
102+
end if
103+
end subroutine handle_error
104+
105+
!> Save access to working directory in settings, in case setting have not been allocated
106+
subroutine get_working_dir(settings, working_dir)
107+
class(fpm_cmd_settings), optional, intent(in) :: settings
108+
character(len=:), allocatable, intent(out) :: working_dir
109+
if (present(settings)) then
110+
working_dir = settings%working_dir
111+
end if
112+
end subroutine get_working_dir
113+
37114
end program main

ci/run_tests.sh

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -13,11 +13,10 @@ fi
1313
pushd example_packages/
1414
rm -rf ./*/build
1515

16-
pushd hello_world
17-
"$fpm" build
18-
"$fpm" run --target hello_world
19-
"$fpm" run
20-
popd
16+
dir=hello_world
17+
"$fpm" -C $dir build
18+
"$fpm" -C $dir run --target hello_world
19+
"$fpm" -C $dir/app run
2120

2221
pushd hello_fpm
2322
"$fpm" build

src/fpm_command_line.f90

Lines changed: 22 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -46,6 +46,7 @@ module fpm_command_line
4646
get_command_line_settings
4747

4848
type, abstract :: fpm_cmd_settings
49+
character(len=:), allocatable :: working_dir
4950
logical :: verbose=.true.
5051
end type
5152

@@ -119,6 +120,7 @@ subroutine get_command_line_settings(cmd_settings)
119120
integer :: i
120121
integer :: widest
121122
type(fpm_install_settings), allocatable :: install_settings
123+
character(len=:), allocatable :: common_args, working_dir
122124

123125
call set_help()
124126
! text for --version switch,
@@ -148,12 +150,14 @@ subroutine get_command_line_settings(cmd_settings)
148150
if(adjustl(cmdarg(1:1)) .ne. '-')exit
149151
enddo
150152

153+
common_args = '--directory:C " " '
154+
151155
! now set subcommand-specific help text and process commandline
152156
! arguments. Then call subcommand routine
153157
select case(trim(cmdarg))
154158

155159
case('run')
156-
call set_args('&
160+
call set_args(common_args //'&
157161
& --target " " &
158162
& --list F &
159163
& --all F &
@@ -206,7 +210,7 @@ subroutine get_command_line_settings(cmd_settings)
206210
& verbose=lget('verbose') )
207211

208212
case('build')
209-
call set_args( '&
213+
call set_args(common_args // '&
210214
& --profile " " &
211215
& --list F &
212216
& --show-model F &
@@ -228,7 +232,7 @@ subroutine get_command_line_settings(cmd_settings)
228232
& verbose=lget('verbose') )
229233

230234
case('new')
231-
call set_args('&
235+
call set_args(common_args // '&
232236
& --src F &
233237
& --lib F &
234238
& --app F &
@@ -298,7 +302,7 @@ subroutine get_command_line_settings(cmd_settings)
298302
endif
299303

300304
case('help','manual')
301-
call set_args('&
305+
call set_args(common_args // '&
302306
& --verbose F &
303307
& ',help_help,version_text)
304308
if(size(unnamed).lt.2)then
@@ -346,7 +350,8 @@ subroutine get_command_line_settings(cmd_settings)
346350
call printhelp(help_text)
347351

348352
case('install')
349-
call set_args('--profile " " --no-rebuild F --verbose F --prefix " " &
353+
call set_args(common_args // '&
354+
& --profile " " --no-rebuild F --verbose F --prefix " " &
350355
& --list F &
351356
& --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
352357
& --flag:: " "&
@@ -371,7 +376,7 @@ subroutine get_command_line_settings(cmd_settings)
371376
call move_alloc(install_settings, cmd_settings)
372377

373378
case('list')
374-
call set_args('&
379+
call set_args(common_args // '&
375380
& --list F&
376381
& --verbose F&
377382
&', help_list, version_text)
@@ -380,7 +385,7 @@ subroutine get_command_line_settings(cmd_settings)
380385
call printhelp(help_list_dash)
381386
endif
382387
case('test')
383-
call set_args('&
388+
call set_args(common_args // '&
384389
& --target " " &
385390
& --list F&
386391
& --profile " "&
@@ -425,7 +430,7 @@ subroutine get_command_line_settings(cmd_settings)
425430
& verbose=lget('verbose') )
426431

427432
case('update')
428-
call set_args('--fetch-only F --verbose F --clean F', &
433+
call set_args(common_args // ' --fetch-only F --verbose F --clean F', &
429434
help_update, version_text)
430435

431436
if( size(unnamed) .gt. 1 )then
@@ -441,7 +446,7 @@ subroutine get_command_line_settings(cmd_settings)
441446

442447
case default
443448

444-
call set_args('&
449+
call set_args(common_args // '&
445450
& --list F&
446451
& --verbose F&
447452
&', help_fpm, version_text)
@@ -462,6 +467,12 @@ subroutine get_command_line_settings(cmd_settings)
462467
call printhelp(help_text)
463468

464469
end select
470+
471+
if (allocated(cmd_settings)) then
472+
working_dir = sget("directory")
473+
call move_alloc(working_dir, cmd_settings%working_dir)
474+
end if
475+
465476
contains
466477

467478
subroutine check_build_vals()
@@ -674,6 +685,8 @@ subroutine set_help()
674685
' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] [options]', &
675686
' ', &
676687
'SUBCOMMAND OPTIONS ', &
688+
' -C, --directory PATH', &
689+
' Change working directory to PATH before running any command', &
677690
' --profile PROF selects the compilation profile for the build.',&
678691
' Currently available profiles are "release" for',&
679692
' high optimization and "debug" for full debug options.',&

src/fpm_filesystem.f90

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,7 @@ module fpm_filesystem
1010
private
1111
public :: basename, canon_path, dirname, is_dir, join_path, number_of_rows, read_lines, list_files, env_variable, &
1212
mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file, to_fortran_name
13-
public :: fileopen, fileclose, filewrite, warnwrite
13+
public :: fileopen, fileclose, filewrite, warnwrite, parent_dir
1414

1515
integer, parameter :: LINE_BUFFER_LEN = 1000
1616

@@ -184,6 +184,15 @@ function dirname(path) result (dir)
184184

185185
end function dirname
186186

187+
!> Extract dirname from path
188+
function parent_dir(path) result (dir)
189+
character(*), intent(in) :: path
190+
character(:), allocatable :: dir
191+
192+
dir = path(1:scan(path,'/\',back=.true.)-1)
193+
194+
end function parent_dir
195+
187196

188197
!> test if a name matches an existing directory path
189198
logical function is_dir(dir)

src/fpm_os.F90

Lines changed: 105 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,105 @@
1+
module fpm_os
2+
use, intrinsic :: iso_c_binding, only : c_char, c_int, c_null_char, c_ptr, c_associated
3+
use fpm_error, only : error_t, fatal_error
4+
implicit none
5+
private
6+
public :: change_directory, get_current_directory
7+
8+
#ifndef _WIN32
9+
character(len=*), parameter :: pwd_env = "PWD"
10+
#else
11+
character(len=*), parameter :: pwd_env = "CD"
12+
#endif
13+
14+
interface
15+
function chdir(path) result(stat) &
16+
#ifndef _WIN32
17+
bind(C, name="chdir")
18+
#else
19+
bind(C, name="_chdir")
20+
#endif
21+
import :: c_char, c_int
22+
character(kind=c_char, len=1), intent(in) :: path(*)
23+
integer(c_int) :: stat
24+
end function chdir
25+
26+
function getcwd(buf, bufsize) result(path) &
27+
#ifndef _WIN32
28+
bind(C, name="getcwd")
29+
#else
30+
bind(C, name="_getcwd")
31+
#endif
32+
import :: c_char, c_int, c_ptr
33+
character(kind=c_char, len=1), intent(in) :: buf(*)
34+
integer(c_int), value, intent(in) :: bufsize
35+
type(c_ptr) :: path
36+
end function getcwd
37+
end interface
38+
39+
contains
40+
41+
subroutine change_directory(path, error)
42+
character(len=*), intent(in) :: path
43+
type(error_t), allocatable, intent(out) :: error
44+
45+
character(kind=c_char, len=1), allocatable :: cpath(:)
46+
integer :: stat
47+
48+
allocate(cpath(len(path)+1))
49+
call f_c_character(path, cpath, len(path)+1)
50+
51+
stat = chdir(cpath)
52+
53+
if (stat /= 0) then
54+
call fatal_error(error, "Failed to change directory to '"//path//"'")
55+
end if
56+
end subroutine change_directory
57+
58+
subroutine get_current_directory(path, error)
59+
character(len=:), allocatable, intent(out) :: path
60+
type(error_t), allocatable, intent(out) :: error
61+
62+
character(kind=c_char, len=1), allocatable :: cpath(:)
63+
integer(c_int), parameter :: buffersize = 1000_c_int
64+
type(c_ptr) :: tmp
65+
66+
allocate(cpath(buffersize))
67+
68+
tmp = getcwd(cpath, buffersize)
69+
if (c_associated(tmp)) then
70+
call c_f_character(cpath, path)
71+
else
72+
call fatal_error(error, "Failed to retrieve current directory")
73+
end if
74+
75+
end subroutine get_current_directory
76+
77+
subroutine f_c_character(rhs, lhs, len)
78+
character(kind=c_char), intent(out) :: lhs(*)
79+
character(len=*), intent(in) :: rhs
80+
integer, intent(in) :: len
81+
integer :: length
82+
length = min(len-1, len_trim(rhs))
83+
84+
lhs(1:length) = transfer(rhs(1:length), lhs(1:length))
85+
lhs(length+1:length+1) = c_null_char
86+
87+
end subroutine f_c_character
88+
89+
subroutine c_f_character(rhs, lhs)
90+
character(kind=c_char), intent(in) :: rhs(*)
91+
character(len=:), allocatable, intent(out) :: lhs
92+
93+
integer :: ii
94+
95+
do ii = 1, huge(ii) - 1
96+
if (rhs(ii) == c_null_char) then
97+
exit
98+
end if
99+
end do
100+
allocate(character(len=ii-1) :: lhs)
101+
lhs = transfer(rhs(1:ii-1), lhs)
102+
103+
end subroutine c_f_character
104+
105+
end module fpm_os

0 commit comments

Comments
 (0)