Skip to content

Commit 6fc695f

Browse files
authored
Merge branch 'master' into master
2 parents 831ab07 + 845217f commit 6fc695f

File tree

6 files changed

+246
-18
lines changed

6 files changed

+246
-18
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_backend.f90

Lines changed: 28 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -27,12 +27,12 @@
2727
!>
2828
module fpm_backend
2929

30-
use fpm_environment, only: run
31-
use fpm_filesystem, only: dirname, join_path, exists, mkdir
30+
use fpm_environment, only: run, get_os_type, OS_WINDOWS
31+
use fpm_filesystem, only: dirname, join_path, exists, mkdir, unix_path
3232
use fpm_model, only: fpm_model_t
3333
use fpm_targets, only: build_target_t, build_target_ptr, FPM_TARGET_OBJECT, &
3434
FPM_TARGET_C_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE
35-
use fpm_strings, only: string_cat
35+
use fpm_strings, only: string_cat, string_t
3636

3737
implicit none
3838

@@ -250,7 +250,16 @@ subroutine build_target(model,target)
250250
//" "//target%link_flags// " -o " // target%output_file)
251251

252252
case (FPM_TARGET_ARCHIVE)
253-
call run(model%archiver // target%output_file // " " // string_cat(target%link_objects," "))
253+
254+
select case (get_os_type())
255+
case (OS_WINDOWS)
256+
call write_response_file(target%output_file//".resp" ,target%link_objects)
257+
call run(model%archiver // target%output_file // " @" // target%output_file//".resp")
258+
259+
case default
260+
call run(model%archiver // target%output_file // " " // string_cat(target%link_objects," "))
261+
262+
end select
254263

255264
end select
256265

@@ -262,4 +271,19 @@ subroutine build_target(model,target)
262271

263272
end subroutine build_target
264273

274+
!> Response files allow to read command line options from files.
275+
!> Whitespace is used to separate the arguments, we will use newlines
276+
!> as separator to create readable response files which can be inspected
277+
!> in case of errors.
278+
subroutine write_response_file(name, argv)
279+
character(len=*), intent(in) :: name
280+
type(string_t), intent(in) :: argv(:)
281+
integer :: iarg, io
282+
open(file=name, newunit=io)
283+
do iarg = 1, size(argv)
284+
write(io, '(a)') unix_path(argv(iarg)%s)
285+
end do
286+
close(io)
287+
end subroutine write_response_file
288+
265289
end module fpm_backend

src/fpm_command_line.f90

Lines changed: 22 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -48,6 +48,7 @@ module fpm_command_line
4848
get_command_line_settings
4949

5050
type, abstract :: fpm_cmd_settings
51+
character(len=:), allocatable :: working_dir
5152
logical :: verbose=.true.
5253
end type
5354

@@ -121,6 +122,7 @@ subroutine get_command_line_settings(cmd_settings)
121122
integer :: i
122123
integer :: widest
123124
type(fpm_install_settings), allocatable :: install_settings
125+
character(len=:), allocatable :: common_args, working_dir
124126

125127
call set_help()
126128
! text for --version switch,
@@ -147,12 +149,14 @@ subroutine get_command_line_settings(cmd_settings)
147149
CLI_RESPONSE_FILE=.true.
148150
cmdarg = get_subcommand()
149151

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

154158
case('run')
155-
call set_args('&
159+
call set_args(common_args //'&
156160
& --target " " &
157161
& --list F &
158162
& --all F &
@@ -205,7 +209,7 @@ subroutine get_command_line_settings(cmd_settings)
205209
& verbose=lget('verbose') )
206210

207211
case('build')
208-
call set_args( '&
212+
call set_args(common_args // '&
209213
& --profile " " &
210214
& --list F &
211215
& --show-model F &
@@ -227,7 +231,7 @@ subroutine get_command_line_settings(cmd_settings)
227231
& verbose=lget('verbose') )
228232

229233
case('new')
230-
call set_args('&
234+
call set_args(common_args // '&
231235
& --src F &
232236
& --lib F &
233237
& --app F &
@@ -297,7 +301,7 @@ subroutine get_command_line_settings(cmd_settings)
297301
endif
298302

299303
case('help','manual')
300-
call set_args('&
304+
call set_args(common_args // '&
301305
& --verbose F &
302306
& ',help_help,version_text)
303307
if(size(unnamed).lt.2)then
@@ -345,7 +349,8 @@ subroutine get_command_line_settings(cmd_settings)
345349
call printhelp(help_text)
346350

347351
case('install')
348-
call set_args('--profile " " --no-rebuild F --verbose F --prefix " " &
352+
call set_args(common_args // '&
353+
& --profile " " --no-rebuild F --verbose F --prefix " " &
349354
& --list F &
350355
& --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
351356
& --flag:: " "&
@@ -370,7 +375,7 @@ subroutine get_command_line_settings(cmd_settings)
370375
call move_alloc(install_settings, cmd_settings)
371376

372377
case('list')
373-
call set_args('&
378+
call set_args(common_args // '&
374379
& --list F&
375380
& --verbose F&
376381
&', help_list, version_text)
@@ -379,7 +384,7 @@ subroutine get_command_line_settings(cmd_settings)
379384
call printhelp(help_list_dash)
380385
endif
381386
case('test')
382-
call set_args('&
387+
call set_args(common_args // '&
383388
& --target " " &
384389
& --list F&
385390
& --profile " "&
@@ -424,7 +429,7 @@ subroutine get_command_line_settings(cmd_settings)
424429
& verbose=lget('verbose') )
425430

426431
case('update')
427-
call set_args('--fetch-only F --verbose F --clean F', &
432+
call set_args(common_args // ' --fetch-only F --verbose F --clean F', &
428433
help_update, version_text)
429434

430435
if( size(unnamed) .gt. 1 )then
@@ -439,6 +444,7 @@ subroutine get_command_line_settings(cmd_settings)
439444
clean=lget('clean'))
440445

441446
case default
447+
442448
if(which('fpm-'//cmdarg).ne.'')then
443449
call run('fpm-'//trim(cmdarg)//' '// get_command_arguments_quoted(),.false.)
444450
else
@@ -464,6 +470,12 @@ subroutine get_command_line_settings(cmd_settings)
464470
endif
465471

466472
end select
473+
474+
if (allocated(cmd_settings)) then
475+
working_dir = sget("directory")
476+
call move_alloc(working_dir, cmd_settings%working_dir)
477+
end if
478+
467479
contains
468480

469481
subroutine check_build_vals()
@@ -676,6 +688,8 @@ subroutine set_help()
676688
' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] [options]', &
677689
' ', &
678690
'SUBCOMMAND OPTIONS ', &
691+
' -C, --directory PATH', &
692+
' Change working directory to PATH before running any command', &
679693
' --profile PROF selects the compilation profile for the build.',&
680694
' Currently available profiles are "release" for',&
681695
' 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
@@ -11,7 +11,7 @@ module fpm_filesystem
1111
private
1212
public :: basename, canon_path, dirname, is_dir, join_path, number_of_rows, read_lines, list_files, env_variable, &
1313
mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file, to_fortran_name
14-
public :: fileopen, fileclose, filewrite, warnwrite
14+
public :: fileopen, fileclose, filewrite, warnwrite, parent_dir
1515
public :: which
1616

1717
integer, parameter :: LINE_BUFFER_LEN = 1000
@@ -187,6 +187,15 @@ function dirname(path) result (dir)
187187

188188
end function dirname
189189

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

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

0 commit comments

Comments
 (0)