Skip to content

Commit 5855337

Browse files
committed
Automatically search for package manifest
1 parent 3c9e610 commit 5855337

File tree

4 files changed

+135
-34
lines changed

4 files changed

+135
-34
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

src/fpm_command_line.f90

Lines changed: 5 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -26,9 +26,7 @@ module fpm_command_line
2626
use fpm_environment, only : get_os_type, get_env, &
2727
OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, &
2828
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD
29-
use fpm_error, only : error_t
3029
use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified
31-
use fpm_os, only : change_directory, get_current_directory
3230
use fpm_strings, only : lower, split, fnv_1a
3331
use fpm_filesystem, only : basename, canon_path, to_fortran_name
3432
use fpm_compiler, only : get_default_compile_flags
@@ -48,6 +46,7 @@ module fpm_command_line
4846
get_command_line_settings
4947

5048
type, abstract :: fpm_cmd_settings
49+
character(len=:), allocatable :: working_dir
5150
logical :: verbose=.true.
5251
end type
5352

@@ -121,9 +120,7 @@ subroutine get_command_line_settings(cmd_settings)
121120
integer :: i
122121
integer :: widest
123122
type(fpm_install_settings), allocatable :: install_settings
124-
character(len=:), allocatable :: pwd_start, working_dir
125-
character(len=:), allocatable :: common_args
126-
type(error_t), allocatable :: error
123+
character(len=:), allocatable :: common_args, working_dir
127124

128125
call set_help()
129126
! text for --version switch,
@@ -153,8 +150,6 @@ subroutine get_command_line_settings(cmd_settings)
153150
if(adjustl(cmdarg(1:1)) .ne. '-')exit
154151
enddo
155152

156-
call get_current_directory(pwd_start)
157-
158153
common_args = '--directory:C " " '
159154

160155
! now set subcommand-specific help text and process commandline
@@ -473,15 +468,9 @@ subroutine get_command_line_settings(cmd_settings)
473468

474469
end select
475470

476-
! Change working directory if requested
477-
working_dir = sget("directory")
478-
if (len_trim(working_dir) > 0) then
479-
call change_directory(working_dir, error)
480-
if (allocated(error)) then
481-
write(stderr, '(*(a, 1x))') "<ERROR>", error%message
482-
stop 1
483-
end if
484-
write(stdout, '(*(a))') "fpm: Entering directory '"//working_dir//"'"
471+
if (allocated(cmd_settings)) then
472+
working_dir = sget("directory")
473+
call move_alloc(working_dir, cmd_settings%working_dir)
485474
end if
486475

487476
contains

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: 43 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
module fpm_os
2-
use, intrinsic :: iso_c_binding, only : c_char, c_int, c_null_char
2+
use, intrinsic :: iso_c_binding, only : c_char, c_int, c_null_char, c_ptr, c_associated
33
use fpm_error, only : error_t, fatal_error
44
implicit none
55
private
@@ -22,6 +22,18 @@ function chdir(path) result(stat) &
2222
character(kind=c_char, len=1), intent(in) :: path(*)
2323
integer(c_int) :: stat
2424
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
2537
end interface
2638

2739
contains
@@ -43,6 +55,25 @@ subroutine change_directory(path, error)
4355
end if
4456
end subroutine change_directory
4557

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+
4677
subroutine f_c_character(rhs, lhs, len)
4778
character(kind=c_char), intent(out) :: lhs(*)
4879
character(len=*), intent(in) :: rhs
@@ -55,25 +86,20 @@ subroutine f_c_character(rhs, lhs, len)
5586

5687
end subroutine f_c_character
5788

58-
subroutine get_current_directory(path)
59-
character(len=:), allocatable, intent(out) :: path
89+
subroutine c_f_character(rhs, lhs)
90+
character(kind=c_char), intent(in) :: rhs(*)
91+
character(len=:), allocatable, intent(out) :: lhs
6092

61-
integer :: length, stat
93+
integer :: ii
6294

63-
call get_environment_variable(pwd_env, length=length, status=stat)
64-
if (stat /= 0) return
65-
66-
allocate(character(len=length) :: path, stat=stat)
67-
if (stat /= 0) return
68-
69-
if (length > 0) then
70-
call get_environment_variable(pwd_env, path, status=stat)
71-
if (stat /= 0) then
72-
deallocate(path)
73-
return
95+
do ii = 1, huge(ii) - 1
96+
if (rhs(ii) == c_null_char) then
97+
exit
7498
end if
75-
end if
99+
end do
100+
allocate(character(len=ii-1) :: lhs)
101+
lhs = transfer(rhs(1:ii-1), lhs)
76102

77-
end subroutine get_current_directory
103+
end subroutine c_f_character
78104

79105
end module fpm_os

0 commit comments

Comments
 (0)