Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
77 changes: 77 additions & 0 deletions app/main.f90
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
program main
use, intrinsic :: iso_fortran_env, only : error_unit, output_unit
use fpm_command_line, only: &
fpm_cmd_settings, &
fpm_new_settings, &
Expand All @@ -8,17 +9,57 @@ program main
fpm_install_settings, &
fpm_update_settings, &
get_command_line_settings
use fpm_error, only: error_t
use fpm_filesystem, only: exists, parent_dir, join_path
use fpm, only: cmd_build, cmd_run
use fpm_cmd_install, only: cmd_install
use fpm_cmd_new, only: cmd_new
use fpm_cmd_update, only : cmd_update
use fpm_os, only: change_directory, get_current_directory

implicit none

class(fpm_cmd_settings), allocatable :: cmd_settings
type(error_t), allocatable :: error
character(len=:), allocatable :: pwd_start, pwd_working, working_dir, project_root

call get_command_line_settings(cmd_settings)

call get_current_directory(pwd_start, error)
call handle_error(error)

call get_working_dir(cmd_settings, working_dir)
if (allocated(working_dir)) then
! Change working directory if requested
if (len_trim(working_dir) > 0) then
call change_directory(working_dir, error)
call handle_error(error)

call get_current_directory(pwd_working, error)
call handle_error(error)
write(output_unit, '(*(a))') "fpm: Entering directory '"//pwd_working//"'"
else
pwd_working = pwd_start
end if
else
pwd_working = pwd_start
end if

if (.not.has_manifest(pwd_working)) then
project_root = pwd_working
do while(.not.has_manifest(project_root))
working_dir = parent_dir(project_root)
if (len(working_dir) == 0) exit
project_root = working_dir
end do

if (has_manifest(project_root)) then
call change_directory(project_root, error)
call handle_error(error)
write(output_unit, '(*(a))') "fpm: Entering directory '"//project_root//"'"
end if
end if

select type(settings=>cmd_settings)
type is (fpm_new_settings)
call cmd_new(settings)
Expand All @@ -34,4 +75,40 @@ program main
call cmd_update(settings)
end select

if (allocated(project_root)) then
write(output_unit, '(*(a))') "fpm: Leaving directory '"//project_root//"'"
end if

if (pwd_start /= pwd_working) then
write(output_unit, '(*(a))') "fpm: Leaving directory '"//pwd_working//"'"
end if

contains

function has_manifest(dir)
character(len=*), intent(in) :: dir
logical :: has_manifest

character(len=:), allocatable :: manifest

has_manifest = exists(join_path(dir, "fpm.toml"))
end function has_manifest

subroutine handle_error(error)
type(error_t), optional, intent(in) :: error
if (present(error)) then
write(error_unit, '("[Error]", 1x, a)') error%message
stop 1
end if
end subroutine handle_error

!> Save access to working directory in settings, in case setting have not been allocated
subroutine get_working_dir(settings, working_dir)
class(fpm_cmd_settings), optional, intent(in) :: settings
character(len=:), allocatable, intent(out) :: working_dir
if (present(settings)) then
working_dir = settings%working_dir
end if
end subroutine get_working_dir

end program main
9 changes: 4 additions & 5 deletions ci/run_tests.sh
Original file line number Diff line number Diff line change
Expand Up @@ -13,11 +13,10 @@ fi
pushd example_packages/
rm -rf ./*/build

pushd hello_world
"$fpm" build
"$fpm" run --target hello_world
"$fpm" run
popd
dir=hello_world
"$fpm" -C $dir build
"$fpm" -C $dir run --target hello_world
"$fpm" -C $dir/app run

pushd hello_fpm
"$fpm" build
Expand Down
31 changes: 22 additions & 9 deletions src/fpm_command_line.f90
Original file line number Diff line number Diff line change
Expand Up @@ -46,6 +46,7 @@ module fpm_command_line
get_command_line_settings

type, abstract :: fpm_cmd_settings
character(len=:), allocatable :: working_dir
logical :: verbose=.true.
end type

Expand Down Expand Up @@ -119,6 +120,7 @@ subroutine get_command_line_settings(cmd_settings)
integer :: i
integer :: widest
type(fpm_install_settings), allocatable :: install_settings
character(len=:), allocatable :: common_args, working_dir

call set_help()
! text for --version switch,
Expand Down Expand Up @@ -148,12 +150,14 @@ subroutine get_command_line_settings(cmd_settings)
if(adjustl(cmdarg(1:1)) .ne. '-')exit
enddo

common_args = '--directory:C " " '

! now set subcommand-specific help text and process commandline
! arguments. Then call subcommand routine
select case(trim(cmdarg))

case('run')
call set_args('&
call set_args(common_args //'&
& --target " " &
& --list F &
& --all F &
Expand Down Expand Up @@ -206,7 +210,7 @@ subroutine get_command_line_settings(cmd_settings)
& verbose=lget('verbose') )

case('build')
call set_args( '&
call set_args(common_args // '&
& --profile " " &
& --list F &
& --show-model F &
Expand All @@ -228,7 +232,7 @@ subroutine get_command_line_settings(cmd_settings)
& verbose=lget('verbose') )

case('new')
call set_args('&
call set_args(common_args // '&
& --src F &
& --lib F &
& --app F &
Expand Down Expand Up @@ -298,7 +302,7 @@ subroutine get_command_line_settings(cmd_settings)
endif

case('help','manual')
call set_args('&
call set_args(common_args // '&
& --verbose F &
& ',help_help,version_text)
if(size(unnamed).lt.2)then
Expand Down Expand Up @@ -346,7 +350,8 @@ subroutine get_command_line_settings(cmd_settings)
call printhelp(help_text)

case('install')
call set_args('--profile " " --no-rebuild F --verbose F --prefix " " &
call set_args(common_args // '&
& --profile " " --no-rebuild F --verbose F --prefix " " &
& --list F &
& --compiler "'//get_env('FPM_COMPILER','gfortran')//'" &
& --flag:: " "&
Expand All @@ -371,7 +376,7 @@ subroutine get_command_line_settings(cmd_settings)
call move_alloc(install_settings, cmd_settings)

case('list')
call set_args('&
call set_args(common_args // '&
& --list F&
& --verbose F&
&', help_list, version_text)
Expand All @@ -380,7 +385,7 @@ subroutine get_command_line_settings(cmd_settings)
call printhelp(help_list_dash)
endif
case('test')
call set_args('&
call set_args(common_args // '&
& --target " " &
& --list F&
& --profile " "&
Expand Down Expand Up @@ -425,7 +430,7 @@ subroutine get_command_line_settings(cmd_settings)
& verbose=lget('verbose') )

case('update')
call set_args('--fetch-only F --verbose F --clean F', &
call set_args(common_args // ' --fetch-only F --verbose F --clean F', &
help_update, version_text)

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

case default

call set_args('&
call set_args(common_args // '&
& --list F&
& --verbose F&
&', help_fpm, version_text)
Expand All @@ -462,6 +467,12 @@ subroutine get_command_line_settings(cmd_settings)
call printhelp(help_text)

end select

if (allocated(cmd_settings)) then
working_dir = sget("directory")
call move_alloc(working_dir, cmd_settings%working_dir)
end if

contains

subroutine check_build_vals()
Expand Down Expand Up @@ -674,6 +685,8 @@ subroutine set_help()
' install [--profile PROF] [--flag FFLAGS] [--no-rebuild] [--prefix PATH] [options]', &
' ', &
'SUBCOMMAND OPTIONS ', &
' -C, --directory PATH', &
' Change working directory to PATH before running any command', &
' --profile PROF selects the compilation profile for the build.',&
' Currently available profiles are "release" for',&
' high optimization and "debug" for full debug options.',&
Expand Down
11 changes: 10 additions & 1 deletion src/fpm_filesystem.f90
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ module fpm_filesystem
private
public :: basename, canon_path, dirname, is_dir, join_path, number_of_rows, read_lines, list_files, env_variable, &
mkdir, exists, get_temp_filename, windows_path, unix_path, getline, delete_file, to_fortran_name
public :: fileopen, fileclose, filewrite, warnwrite
public :: fileopen, fileclose, filewrite, warnwrite, parent_dir

integer, parameter :: LINE_BUFFER_LEN = 1000

Expand Down Expand Up @@ -184,6 +184,15 @@ function dirname(path) result (dir)

end function dirname

!> Extract dirname from path
function parent_dir(path) result (dir)
character(*), intent(in) :: path
character(:), allocatable :: dir

dir = path(1:scan(path,'/\',back=.true.)-1)

end function parent_dir


!> test if a name matches an existing directory path
logical function is_dir(dir)
Expand Down
105 changes: 105 additions & 0 deletions src/fpm_os.F90
Original file line number Diff line number Diff line change
@@ -0,0 +1,105 @@
module fpm_os
use, intrinsic :: iso_c_binding, only : c_char, c_int, c_null_char, c_ptr, c_associated
use fpm_error, only : error_t, fatal_error
implicit none
private
public :: change_directory, get_current_directory

#ifndef _WIN32
character(len=*), parameter :: pwd_env = "PWD"
#else
character(len=*), parameter :: pwd_env = "CD"
#endif

interface
function chdir(path) result(stat) &
#ifndef _WIN32
bind(C, name="chdir")
#else
bind(C, name="_chdir")
#endif
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

It's fine for this PR, but down the road we should move all these platform specific ifdefs into a platform.f90 or compatibility.f90 file, and then just use such a file here.

Copy link
Member Author

@awvwgk awvwgk May 27, 2021

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I was tempted to do:

#ifndef _WIN32
character(len=*), parameter :: chdir_symbol = "chdir"
#else
character(len=*), parameter :: chdir_symbol = "_chdir"
#endif
! ...
function chdir(...) bind(C, name=chdir_symbol)

But GFortran didn't like those, unfortunately.

Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I was going to try exactly that to see if it works! Then we could have the chdir_symbol in platform.f90. As it is now, we'll have to move the whole chdir definition into platform.f90, which is fine too.

Copy link
Member Author

@awvwgk awvwgk May 27, 2021

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I used string concatenation in the past with bind(C, name=namespace//"...") so in principle this seems to work. But here I'm hitting:

./src/fpm_os.F90:18:29:

   18 |                 bind(C, name=chdir_symbol)
      |                             1
Error: Parameter ‘chdir_symbol’ at (1) has not been declared or is a variable, which does not reduce to a constant expression

Copy link
Member Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Maybe this is not possible because the interface is a separate scoping unit not automatically inheriting the module scope. Using import will also not work here because it would make the parameter available after it has been used. That's a tricky one, maybe worth a thread on discourse?

Copy link
Member Author

@awvwgk awvwgk May 27, 2021

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Posted here: https://fortran-lang.discourse.group/t/constant-expressions-for-bind-c-name/1319

Let's see if somebody more knowledgeable in the Fortran standard can help us out here.

import :: c_char, c_int
character(kind=c_char, len=1), intent(in) :: path(*)
integer(c_int) :: stat
end function chdir

function getcwd(buf, bufsize) result(path) &
#ifndef _WIN32
bind(C, name="getcwd")
#else
bind(C, name="_getcwd")
#endif
import :: c_char, c_int, c_ptr
character(kind=c_char, len=1), intent(in) :: buf(*)
integer(c_int), value, intent(in) :: bufsize
type(c_ptr) :: path
end function getcwd
end interface

contains

subroutine change_directory(path, error)
character(len=*), intent(in) :: path
type(error_t), allocatable, intent(out) :: error

character(kind=c_char, len=1), allocatable :: cpath(:)
integer :: stat

allocate(cpath(len(path)+1))
call f_c_character(path, cpath, len(path)+1)

stat = chdir(cpath)

if (stat /= 0) then
call fatal_error(error, "Failed to change directory to '"//path//"'")
end if
end subroutine change_directory

subroutine get_current_directory(path, error)
character(len=:), allocatable, intent(out) :: path
type(error_t), allocatable, intent(out) :: error

character(kind=c_char, len=1), allocatable :: cpath(:)
integer(c_int), parameter :: buffersize = 1000_c_int
type(c_ptr) :: tmp

allocate(cpath(buffersize))

tmp = getcwd(cpath, buffersize)
if (c_associated(tmp)) then
call c_f_character(cpath, path)
else
call fatal_error(error, "Failed to retrieve current directory")
end if

end subroutine get_current_directory

subroutine f_c_character(rhs, lhs, len)
character(kind=c_char), intent(out) :: lhs(*)
character(len=*), intent(in) :: rhs
integer, intent(in) :: len
integer :: length
length = min(len-1, len_trim(rhs))

lhs(1:length) = transfer(rhs(1:length), lhs(1:length))
lhs(length+1:length+1) = c_null_char

end subroutine f_c_character

subroutine c_f_character(rhs, lhs)
character(kind=c_char), intent(in) :: rhs(*)
character(len=:), allocatable, intent(out) :: lhs

integer :: ii

do ii = 1, huge(ii) - 1
if (rhs(ii) == c_null_char) then
exit
end if
end do
allocate(character(len=ii-1) :: lhs)
lhs = transfer(rhs(1:ii-1), lhs)

end subroutine c_f_character

end module fpm_os