11program main
2+ use , intrinsic :: iso_fortran_env, only : error_unit, output_unit
23use 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
1114use fpm, only: cmd_build, cmd_run
1215use fpm_cmd_install, only: cmd_install
1316use fpm_cmd_new, only: cmd_new
1417use fpm_cmd_update, only : cmd_update
18+ use fpm_os, only: change_directory, get_current_directory
1519
1620implicit none
1721
1822class(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
2026call 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+
2263select type (settings= >cmd_settings)
2364type is (fpm_new_settings)
2465 call cmd_new(settings)
@@ -34,4 +75,40 @@ program main
3475 call cmd_update(settings)
3576end 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+
37114end program main
0 commit comments