From c58584e725b904d74743c6eb2b07e372fc539b39 Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Sat, 17 Apr 2021 13:01:18 +0200 Subject: Allow usage of response files with ar --- src/fpm_backend.f90 | 20 ++++++++++++++++++-- 1 file changed, 18 insertions(+), 2 deletions(-) diff --git a/src/fpm_backend.f90 b/src/fpm_backend.f90 index 74cef61..4b19e25 100644 --- a/src/fpm_backend.f90 +++ b/src/fpm_backend.f90 @@ -33,7 +33,7 @@ use fpm_model, only: fpm_model_t use fpm_targets, only: build_target_t, build_target_ptr, & FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE -use fpm_strings, only: string_cat +use fpm_strings, only: string_t implicit none @@ -247,7 +247,8 @@ subroutine build_target(model,target) //" "//target%link_flags// " -o " // target%output_file) case (FPM_TARGET_ARCHIVE) - call run("ar -rs " // target%output_file // " " // string_cat(target%link_objects," ")) + call write_response_file(target%output_file//".resp" ,target%link_objects) + call run("ar -rs " // target%output_file // " @" // target%output_file//".resp") end select @@ -259,4 +260,19 @@ subroutine build_target(model,target) end subroutine build_target +!> Response files allow to read command line options from files. +!> Whitespace is used to separate the arguments, we will use newlines +!> as separator to create readable response files which can be inspected +!> in case of errors. +subroutine write_response_file(name, argv) + character(len=*), intent(in) :: name + type(string_t), intent(in) :: argv(:) + integer :: iarg, io + open(file=name, newunit=io) + do iarg = 1, size(argv) + write(io, '(a)') argv(iarg)%s + end do + close(io) +end subroutine write_response_file + end module fpm_backend -- cgit v1.2.3 From 7a8f33721974cb66d44834229aff6dd4e2031eda Mon Sep 17 00:00:00 2001 From: LKedward Date: Sat, 17 Apr 2021 12:27:09 +0100 Subject: Use response files on Windows but with unix_path --- src/fpm_backend.f90 | 20 ++++++++++++++------ 1 file changed, 14 insertions(+), 6 deletions(-) diff --git a/src/fpm_backend.f90 b/src/fpm_backend.f90 index 4b19e25..21e7983 100644 --- a/src/fpm_backend.f90 +++ b/src/fpm_backend.f90 @@ -27,13 +27,13 @@ !> module fpm_backend -use fpm_environment, only: run -use fpm_filesystem, only: dirname, join_path, exists, mkdir +use fpm_environment, only: run, get_os_type, OS_WINDOWS +use fpm_filesystem, only: dirname, join_path, exists, mkdir, unix_path use fpm_model, only: fpm_model_t use fpm_targets, only: build_target_t, build_target_ptr, & FPM_TARGET_OBJECT, FPM_TARGET_ARCHIVE, FPM_TARGET_EXECUTABLE -use fpm_strings, only: string_t +use fpm_strings, only: string_cat, string_t implicit none @@ -247,8 +247,16 @@ subroutine build_target(model,target) //" "//target%link_flags// " -o " // target%output_file) case (FPM_TARGET_ARCHIVE) - call write_response_file(target%output_file//".resp" ,target%link_objects) - call run("ar -rs " // target%output_file // " @" // target%output_file//".resp") + + select case (get_os_type()) + case (OS_WINDOWS) + call write_response_file(target%output_file//".resp" ,target%link_objects) + call run("ar -rs " // target%output_file // " @" // target%output_file//".resp") + + case default + call run("ar -rs " // target%output_file // " " // string_cat(target%link_objects," ")) + + end select end select @@ -270,7 +278,7 @@ subroutine write_response_file(name, argv) integer :: iarg, io open(file=name, newunit=io) do iarg = 1, size(argv) - write(io, '(a)') argv(iarg)%s + write(io, '(a)') unix_path(argv(iarg)%s) end do close(io) end subroutine write_response_file -- cgit v1.2.3 From 3c9e6105c8458f6a59d2edc6fd7f2e79c18de943 Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Thu, 27 May 2021 20:04:51 +0200 Subject: Allow fpm to change the working directory --- ci/run_tests.sh | 144 +++++++++++++++++++++-------------------------- src/fpm_command_line.f90 | 42 +++++++++++--- src/fpm_os.F90 | 79 ++++++++++++++++++++++++++ 3 files changed, 176 insertions(+), 89 deletions(-) create mode 100644 src/fpm_os.F90 diff --git a/ci/run_tests.sh b/ci/run_tests.sh index ffcd9c2..a31fa18 100755 --- a/ci/run_tests.sh +++ b/ci/run_tests.sh @@ -13,86 +13,70 @@ fi pushd example_packages/ rm -rf ./*/build -pushd hello_world -"$fpm" build -"$fpm" run --target hello_world -"$fpm" run -popd - -pushd hello_fpm -"$fpm" build -"$fpm" run --target hello_fpm -popd - -pushd circular_test -"$fpm" build -popd - -pushd circular_example -"$fpm" build -popd - -pushd hello_complex -"$fpm" build -"$fpm" test -"$fpm" run --target say_Hello -"$fpm" run --target say_goodbye -"$fpm" test --target greet_test -"$fpm" test --target farewell_test -popd - -pushd hello_complex_2 -"$fpm" build -"$fpm" run --target say_hello_world -"$fpm" run --target say_goodbye -"$fpm" test --target greet_test -"$fpm" test --target farewell_test -popd - -pushd with_examples -"$fpm" build -"$fpm" run --example --target demo-prog -"$fpm" run --target demo-prog -popd - -pushd auto_discovery_off -"$fpm" build -"$fpm" run --target auto_discovery_off -"$fpm" test --target my_test -test ! -x ./build/gfortran_*/app/unused -test ! -x ./build/gfortran_*/test/unused_test -popd - -pushd with_c -"$fpm" build -"$fpm" run --target with_c -popd - -pushd submodules -"$fpm" build -popd - -pushd program_with_module -"$fpm" build -"$fpm" run --target Program_with_module -popd - -pushd link_executable -"$fpm" build -"$fpm" run --target gomp_test -popd - -pushd fortran_includes -"$fpm" build -popd - -pushd c_includes -"$fpm" build -popd - -pushd c_header_only -"$fpm" build -popd +dir=hello_world +"$fpm" -C $dir build +"$fpm" -C $dir run --target hello_world +"$fpm" -C $dir run + +dir=hello_fpm +"$fpm" -C $dir build +"$fpm" -C $dir run --target hello_fpm + +dir=circular_test +"$fpm" -C $dir build + +dir=circular_example +"$fpm" -C $dir build + +dir=hello_complex +"$fpm" -C $dir build +"$fpm" -C $dir test +"$fpm" -C $dir run --target say_Hello +"$fpm" -C $dir run --target say_goodbye +"$fpm" -C $dir test --target greet_test +"$fpm" -C $dir test --target farewell_test + +dir=hello_complex_2 +"$fpm" -C $dir build +"$fpm" -C $dir run --target say_hello_world +"$fpm" -C $dir run --target say_goodbye +"$fpm" -C $dir test --target greet_test +"$fpm" -C $dir test --target farewell_test + +dir=with_examples +"$fpm" -C $dir build +"$fpm" -C $dir run --example --target demo-prog +"$fpm" -C $dir run --target demo-prog + +dir=auto_discovery_off +"$fpm" -C $dir build +"$fpm" -C $dir run --target auto_discovery_off +"$fpm" -C $dir test --target my_test +test ! -x $dir/build/gfortran_*/app/unused +test ! -x $dir/build/gfortran_*/test/unused_test + +dir=with_c +"$fpm" -C $dir build +"$fpm" -C $dir run --target with_c + +"$fpm" -C $dir build + +dir=program_with_module +"$fpm" -C $dir build +"$fpm" -C $dir run --target Program_with_module + +dir=link_executable +"$fpm" -C $dir build +"$fpm" -C $dir run --target gomp_test + +dir=fortran_includes +"$fpm" -C $dir build + +dir=c_includes +"$fpm" -C $dir build + +dir=c_header_only +"$fpm" -C $dir build # Cleanup rm -rf ./*/build diff --git a/src/fpm_command_line.f90 b/src/fpm_command_line.f90 index 2a2ecf5..095a533 100644 --- a/src/fpm_command_line.f90 +++ b/src/fpm_command_line.f90 @@ -26,7 +26,9 @@ module fpm_command_line use fpm_environment, only : get_os_type, get_env, & OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, & OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD +use fpm_error, only : error_t use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified +use fpm_os, only : change_directory, get_current_directory use fpm_strings, only : lower, split, fnv_1a use fpm_filesystem, only : basename, canon_path, to_fortran_name use fpm_compiler, only : get_default_compile_flags @@ -119,6 +121,9 @@ contains integer :: i integer :: widest type(fpm_install_settings), allocatable :: install_settings + character(len=:), allocatable :: pwd_start, working_dir + character(len=:), allocatable :: common_args + type(error_t), allocatable :: error call set_help() ! text for --version switch, @@ -148,12 +153,16 @@ contains if(adjustl(cmdarg(1:1)) .ne. '-')exit enddo + call get_current_directory(pwd_start) + + 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 & @@ -206,7 +215,7 @@ contains & verbose=lget('verbose') ) case('build') - call set_args( '& + call set_args(common_args // '& & --profile " " & & --list F & & --show-model F & @@ -228,7 +237,7 @@ contains & verbose=lget('verbose') ) case('new') - call set_args('& + call set_args(common_args // '& & --src F & & --lib F & & --app F & @@ -298,7 +307,7 @@ contains endif case('help','manual') - call set_args('& + call set_args(common_args // '& & --verbose F & & ',help_help,version_text) if(size(unnamed).lt.2)then @@ -346,7 +355,8 @@ contains 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:: " "& @@ -371,7 +381,7 @@ contains 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) @@ -380,7 +390,7 @@ contains call printhelp(help_list_dash) endif case('test') - call set_args('& + call set_args(common_args // '& & --target " " & & --list F& & --profile " "& @@ -425,7 +435,7 @@ contains & 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 @@ -441,7 +451,7 @@ contains case default - call set_args('& + call set_args(common_args // '& & --list F& & --verbose F& &', help_fpm, version_text) @@ -462,6 +472,18 @@ contains call printhelp(help_text) end select + + ! Change working directory if requested + working_dir = sget("directory") + if (len_trim(working_dir) > 0) then + call change_directory(working_dir, error) + if (allocated(error)) then + write(stderr, '(*(a, 1x))') "", error%message + stop 1 + end if + write(stdout, '(*(a))') "fpm: Entering directory '"//working_dir//"'" + end if + contains subroutine check_build_vals() @@ -674,6 +696,8 @@ contains ' 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.',& diff --git a/src/fpm_os.F90 b/src/fpm_os.F90 new file mode 100644 index 0000000..825df58 --- /dev/null +++ b/src/fpm_os.F90 @@ -0,0 +1,79 @@ +module fpm_os + use, intrinsic :: iso_c_binding, only : c_char, c_int, c_null_char + 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 + import :: c_char, c_int + character(kind=c_char, len=1), intent(in) :: path(*) + integer(c_int) :: stat + end function chdir + 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 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 get_current_directory(path) + character(len=:), allocatable, intent(out) :: path + + integer :: length, stat + + call get_environment_variable(pwd_env, length=length, status=stat) + if (stat /= 0) return + + allocate(character(len=length) :: path, stat=stat) + if (stat /= 0) return + + if (length > 0) then + call get_environment_variable(pwd_env, path, status=stat) + if (stat /= 0) then + deallocate(path) + return + end if + end if + + end subroutine get_current_directory + +end module fpm_os -- cgit v1.2.3 From 5855337167b53abcaa17452ea1c3c048acb34e09 Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Thu, 27 May 2021 21:40:35 +0200 Subject: Automatically search for package manifest --- app/main.f90 | 77 ++++++++++++++++++++++++++++++++++++++++++++++++ src/fpm_command_line.f90 | 21 ++++--------- src/fpm_filesystem.f90 | 11 ++++++- src/fpm_os.F90 | 60 ++++++++++++++++++++++++++----------- 4 files changed, 135 insertions(+), 34 deletions(-) diff --git a/app/main.f90 b/app/main.f90 index 7476df6..5600f98 100644 --- a/app/main.f90 +++ b/app/main.f90 @@ -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, & @@ -8,17 +9,57 @@ use fpm_command_line, only: & 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) @@ -34,4 +75,40 @@ type is (fpm_update_settings) 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 diff --git a/src/fpm_command_line.f90 b/src/fpm_command_line.f90 index 095a533..f44bcd0 100644 --- a/src/fpm_command_line.f90 +++ b/src/fpm_command_line.f90 @@ -26,9 +26,7 @@ module fpm_command_line use fpm_environment, only : get_os_type, get_env, & OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, & OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD -use fpm_error, only : error_t use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified -use fpm_os, only : change_directory, get_current_directory use fpm_strings, only : lower, split, fnv_1a use fpm_filesystem, only : basename, canon_path, to_fortran_name use fpm_compiler, only : get_default_compile_flags @@ -48,6 +46,7 @@ public :: fpm_cmd_settings, & get_command_line_settings type, abstract :: fpm_cmd_settings + character(len=:), allocatable :: working_dir logical :: verbose=.true. end type @@ -121,9 +120,7 @@ contains integer :: i integer :: widest type(fpm_install_settings), allocatable :: install_settings - character(len=:), allocatable :: pwd_start, working_dir - character(len=:), allocatable :: common_args - type(error_t), allocatable :: error + character(len=:), allocatable :: common_args, working_dir call set_help() ! text for --version switch, @@ -153,8 +150,6 @@ contains if(adjustl(cmdarg(1:1)) .ne. '-')exit enddo - call get_current_directory(pwd_start) - common_args = '--directory:C " " ' ! now set subcommand-specific help text and process commandline @@ -473,15 +468,9 @@ contains end select - ! Change working directory if requested - working_dir = sget("directory") - if (len_trim(working_dir) > 0) then - call change_directory(working_dir, error) - if (allocated(error)) then - write(stderr, '(*(a, 1x))') "", error%message - stop 1 - end if - write(stdout, '(*(a))') "fpm: Entering directory '"//working_dir//"'" + if (allocated(cmd_settings)) then + working_dir = sget("directory") + call move_alloc(working_dir, cmd_settings%working_dir) end if contains diff --git a/src/fpm_filesystem.f90 b/src/fpm_filesystem.f90 index 28c3b33..c9c97dd 100644 --- a/src/fpm_filesystem.f90 +++ b/src/fpm_filesystem.f90 @@ -10,7 +10,7 @@ use,intrinsic :: iso_fortran_env, only : stdin=>input_unit, stdout=>output_unit, 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 @@ -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) diff --git a/src/fpm_os.F90 b/src/fpm_os.F90 index 825df58..71663fe 100644 --- a/src/fpm_os.F90 +++ b/src/fpm_os.F90 @@ -1,5 +1,5 @@ module fpm_os - use, intrinsic :: iso_c_binding, only : c_char, c_int, c_null_char + 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 @@ -22,6 +22,18 @@ module fpm_os 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 @@ -43,6 +55,25 @@ contains 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 @@ -55,25 +86,20 @@ contains end subroutine f_c_character - subroutine get_current_directory(path) - character(len=:), allocatable, intent(out) :: path + subroutine c_f_character(rhs, lhs) + character(kind=c_char), intent(in) :: rhs(*) + character(len=:), allocatable, intent(out) :: lhs - integer :: length, stat + integer :: ii - call get_environment_variable(pwd_env, length=length, status=stat) - if (stat /= 0) return - - allocate(character(len=length) :: path, stat=stat) - if (stat /= 0) return - - if (length > 0) then - call get_environment_variable(pwd_env, path, status=stat) - if (stat /= 0) then - deallocate(path) - return + do ii = 1, huge(ii) - 1 + if (rhs(ii) == c_null_char) then + exit end if - end if + end do + allocate(character(len=ii-1) :: lhs) + lhs = transfer(rhs(1:ii-1), lhs) - end subroutine get_current_directory + end subroutine c_f_character end module fpm_os -- cgit v1.2.3 From f6eed99634609851afe1af9d1c44412d966381fe Mon Sep 17 00:00:00 2001 From: Sebastian Ehlert <28669218+awvwgk@users.noreply.github.com> Date: Thu, 3 Jun 2021 12:18:36 +0200 Subject: Only test changing directories for one package --- ci/run_tests.sh | 137 +++++++++++++++++++++++++++++++------------------------- 1 file changed, 76 insertions(+), 61 deletions(-) diff --git a/ci/run_tests.sh b/ci/run_tests.sh index a31fa18..9db88e8 100755 --- a/ci/run_tests.sh +++ b/ci/run_tests.sh @@ -16,67 +16,82 @@ rm -rf ./*/build dir=hello_world "$fpm" -C $dir build "$fpm" -C $dir run --target hello_world -"$fpm" -C $dir run - -dir=hello_fpm -"$fpm" -C $dir build -"$fpm" -C $dir run --target hello_fpm - -dir=circular_test -"$fpm" -C $dir build - -dir=circular_example -"$fpm" -C $dir build - -dir=hello_complex -"$fpm" -C $dir build -"$fpm" -C $dir test -"$fpm" -C $dir run --target say_Hello -"$fpm" -C $dir run --target say_goodbye -"$fpm" -C $dir test --target greet_test -"$fpm" -C $dir test --target farewell_test - -dir=hello_complex_2 -"$fpm" -C $dir build -"$fpm" -C $dir run --target say_hello_world -"$fpm" -C $dir run --target say_goodbye -"$fpm" -C $dir test --target greet_test -"$fpm" -C $dir test --target farewell_test - -dir=with_examples -"$fpm" -C $dir build -"$fpm" -C $dir run --example --target demo-prog -"$fpm" -C $dir run --target demo-prog - -dir=auto_discovery_off -"$fpm" -C $dir build -"$fpm" -C $dir run --target auto_discovery_off -"$fpm" -C $dir test --target my_test -test ! -x $dir/build/gfortran_*/app/unused -test ! -x $dir/build/gfortran_*/test/unused_test - -dir=with_c -"$fpm" -C $dir build -"$fpm" -C $dir run --target with_c - -"$fpm" -C $dir build - -dir=program_with_module -"$fpm" -C $dir build -"$fpm" -C $dir run --target Program_with_module - -dir=link_executable -"$fpm" -C $dir build -"$fpm" -C $dir run --target gomp_test - -dir=fortran_includes -"$fpm" -C $dir build - -dir=c_includes -"$fpm" -C $dir build - -dir=c_header_only -"$fpm" -C $dir build +"$fpm" -C $dir/app run + +pushd hello_fpm +"$fpm" build +"$fpm" run --target hello_fpm +popd + +pushd circular_test +"$fpm" build +popd + +pushd circular_example +"$fpm" build +popd + +pushd hello_complex +"$fpm" build +"$fpm" test +"$fpm" run --target say_Hello +"$fpm" run --target say_goodbye +"$fpm" test --target greet_test +"$fpm" test --target farewell_test +popd + +pushd hello_complex_2 +"$fpm" build +"$fpm" run --target say_hello_world +"$fpm" run --target say_goodbye +"$fpm" test --target greet_test +"$fpm" test --target farewell_test +popd + +pushd with_examples +"$fpm" build +"$fpm" run --example --target demo-prog +"$fpm" run --target demo-prog +popd + +pushd auto_discovery_off +"$fpm" build +"$fpm" run --target auto_discovery_off +"$fpm" test --target my_test +test ! -x ./build/gfortran_*/app/unused +test ! -x ./build/gfortran_*/test/unused_test +popd + +pushd with_c +"$fpm" build +"$fpm" run --target with_c +popd + +pushd submodules +"$fpm" build +popd + +pushd program_with_module +"$fpm" build +"$fpm" run --target Program_with_module +popd + +pushd link_executable +"$fpm" build +"$fpm" run --target gomp_test +popd + +pushd fortran_includes +"$fpm" build +popd + +pushd c_includes +"$fpm" build +popd + +pushd c_header_only +"$fpm" build +popd # Cleanup rm -rf ./*/build -- cgit v1.2.3