Skip to content

Commit 481f1ab

Browse files
committed
Merge remote-tracking branch 'fpm/main' into custom-path-to-config
2 parents 01c4224 + 88ebb0a commit 481f1ab

File tree

13 files changed

+179
-57
lines changed

13 files changed

+179
-57
lines changed

.github/workflows/meta.yml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -35,9 +35,9 @@ jobs:
3535
mpi: openmpi
3636
- os: ubuntu-latest
3737
mpi: mpich
38-
- os: macos-latest
38+
- os: macos-12
3939
mpi: openmpi
40-
- os: macos-latest
40+
- os: macos-12
4141
mpi: mpich
4242

4343

ci/run_tests.sh

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -58,6 +58,13 @@ pushd with_examples
5858
"$fpm" run --target demo-prog
5959
popd
6060

61+
pushd many_examples
62+
"$fpm" build
63+
"$fpm" run --example --all
64+
test -e demo1.txt
65+
test -e demo2.txt
66+
popd
67+
6168
pushd auto_discovery_off
6269
"$fpm" build
6370
"$fpm" run --target auto_discovery_off
Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1 @@
1+
/build/*
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
program demo
2+
write(*, '(a)') "This is a simple program"
3+
end program demo
Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
program demo
2+
integer :: i
3+
open(newunit=i,file="demo1.txt",form="formatted",action="write")
4+
write(i, '(a)') "DEMO1"
5+
close(i)
6+
stop 0
7+
end program demo
Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
program demo
2+
integer :: i
3+
open(newunit=i,file="demo2.txt",form="formatted",action="write")
4+
write(i, '(a)') "DEMO2"
5+
close(i)
6+
stop 0
7+
end program demo
Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,12 @@
1+
name = "many_examples"
2+
build.auto-examples = false
3+
4+
[[example]]
5+
name = "demo-1"
6+
source-dir = "demo1"
7+
main = "prog.f90"
8+
9+
[[example]]
10+
name = "demo-2"
11+
source-dir = "demo2"
12+
main = "prog.f90"

src/fpm.f90

Lines changed: 106 additions & 43 deletions
Original file line numberDiff line numberDiff line change
@@ -485,7 +485,7 @@ subroutine cmd_run(settings,test)
485485
type(build_target_t), pointer :: exe_target
486486
type(srcfile_t), pointer :: exe_source
487487
integer :: run_scope,firsterror
488-
integer, allocatable :: stat(:)
488+
integer, allocatable :: stat(:),target_ID(:)
489489
character(len=:),allocatable :: line
490490
logical :: toomany
491491

@@ -513,48 +513,31 @@ subroutine cmd_run(settings,test)
513513
! Enumerate executable targets to run
514514
col_width = -1
515515
found(:) = .false.
516-
allocate(executables(size(settings%name)))
517-
do i=1,size(targets)
518-
516+
allocate(executables(size(targets)),target_ID(size(targets)))
517+
enumerate: do i=1,size(targets)
519518
exe_target => targets(i)%ptr
520-
521-
if (exe_target%target_type == FPM_TARGET_EXECUTABLE .and. &
522-
allocated(exe_target%dependencies)) then
523-
519+
if (should_be_run(settings,run_scope,exe_target)) then
520+
524521
exe_source => exe_target%dependencies(1)%ptr%source
525-
526-
if (exe_source%unit_scope == run_scope) then
527-
528-
col_width = max(col_width,len(basename(exe_target%output_file))+2)
529-
530-
if (size(settings%name) == 0) then
531-
532-
exe_cmd%s = exe_target%output_file
533-
executables = [executables, exe_cmd]
534-
535-
else
536-
537-
do j=1,size(settings%name)
538-
539-
if (glob(trim(exe_source%exe_name),trim(settings%name(j))) .and. .not.found(j)) then
540-
541-
542-
found(j) = .true.
543-
exe_cmd%s = exe_target%output_file
544-
executables(j) = exe_cmd
545-
546-
end if
547-
548-
end do
549-
550-
end if
551-
552-
end if
553-
554-
end if
555-
556-
end do
557-
522+
523+
col_width = max(col_width,len(basename(exe_target%output_file))+2)
524+
525+
! Priority by name ID, or 0 if no name present (run first)
526+
j = settings%name_ID(exe_source%exe_name)
527+
target_ID(i) = j
528+
if (j>0) found(j) = .true.
529+
530+
exe_cmd%s = exe_target%output_file
531+
executables(i) = exe_cmd
532+
533+
else
534+
target_ID(i) = huge(target_ID(i))
535+
endif
536+
end do enumerate
537+
538+
! sort executables by ascending name ID, resize
539+
call sort_executables(target_ID,executables)
540+
558541
! Check if any apps/tests were found
559542
if (col_width < 0) then
560543
if (test) then
@@ -564,8 +547,6 @@ subroutine cmd_run(settings,test)
564547
end if
565548
end if
566549

567-
568-
569550
! Check all names are valid
570551
! or no name and found more than one file
571552
toomany= size(settings%name)==0 .and. size(executables)>1
@@ -736,4 +717,86 @@ subroutine cmd_clean(settings)
736717
end if
737718
end subroutine cmd_clean
738719

720+
!> Sort executables by namelist ID, and trim unused values
721+
pure subroutine sort_executables(target_ID,executables)
722+
integer, allocatable, intent(inout) :: target_ID(:)
723+
type(string_t), allocatable, intent(inout) :: executables(:)
724+
725+
integer :: i,j,n,used
726+
727+
n = size(target_ID)
728+
used = 0
729+
730+
sort: do i=1,n
731+
do j=i+1,n
732+
if (target_ID(j)<target_ID(i)) &
733+
call swap(target_ID(i),target_ID(j),executables(i),executables(j))
734+
end do
735+
if (target_ID(i)<huge(target_ID(i))) used = i
736+
end do sort
737+
738+
if (used>0 .and. used<n) then
739+
target_ID = target_ID(1:used)
740+
executables = executables(1:used)
741+
end if
742+
743+
contains
744+
745+
elemental subroutine swap(t1,t2,e1,e2)
746+
integer, intent(inout) :: t1,t2
747+
type(string_t), intent(inout) :: e1,e2
748+
integer :: tmp
749+
type(string_t) :: etmp
750+
751+
tmp = t1
752+
t1 = t2
753+
t2 = tmp
754+
etmp = e1
755+
e1 = e2
756+
e2 = etmp
757+
end subroutine swap
758+
759+
end subroutine sort_executables
760+
761+
!> Check if an executable should be run
762+
logical function should_be_run(settings,run_scope,exe_target)
763+
class(fpm_run_settings), intent(in) :: settings
764+
integer, intent(in) :: run_scope
765+
type(build_target_t), intent(in) :: exe_target
766+
767+
integer :: j
768+
769+
if (exe_target%target_type == FPM_TARGET_EXECUTABLE .and. &
770+
allocated(exe_target%dependencies)) then
771+
772+
associate(exe_source => exe_target%dependencies(1)%ptr%source)
773+
774+
if (exe_source%unit_scope/=run_scope) then
775+
776+
! Other scope
777+
should_be_run = .false.
778+
779+
elseif (size(settings%name) == 0 .or. .not.settings%list) then
780+
781+
! No list of targets
782+
should_be_run = .true.
783+
784+
else
785+
786+
! Is found in list
787+
should_be_run = settings%name_ID(exe_source%exe_name)>0
788+
789+
end if
790+
791+
end associate
792+
793+
else
794+
795+
!> Invalid target
796+
should_be_run = .false.
797+
798+
endif
799+
800+
end function should_be_run
801+
739802
end module fpm

src/fpm/git.f90

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -441,11 +441,12 @@ subroutine git_archive(source, destination, ref, additional_files, verbose, erro
441441
endif
442442

443443
call run('git archive '//ref//' &
444-
--format='//archive_format// &
445-
add_files//' \
446-
-o '//destination, \
447-
echo=verbose, \
448-
exitstat=stat)
444+
& --format='//archive_format// &
445+
& add_files//' &
446+
& -o '//destination, &
447+
& echo=verbose, &
448+
& exitstat=stat)
449+
449450
if (stat /= 0) then
450451
call fatal_error(error, "Error packing '"//source//"'."); return
451452
end if

src/fpm/manifest/preprocess.f90

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -58,10 +58,6 @@ module fpm_manifest_preprocess
5858

5959
character(*), parameter, private :: class_name = 'preprocess_config_t'
6060

61-
interface operator(==)
62-
module procedure preprocess_is_same
63-
end interface
64-
6561
contains
6662

6763
!> Construct a new preprocess configuration from TOML data structure
@@ -208,7 +204,6 @@ logical function preprocess_is_same(this,that)
208204

209205
integer :: istr
210206

211-
212207
preprocess_is_same = .false.
213208

214209
select type (other=>that)

src/fpm_command_line.f90

Lines changed: 25 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,8 @@ module fpm_command_line
2828
OS_CYGWIN, OS_SOLARIS, OS_FREEBSD, OS_OPENBSD, OS_NAME
2929
use M_CLI2, only : set_args, lget, sget, unnamed, remaining, specified
3030
use M_CLI2, only : get_subcommand, CLI_RESPONSE_FILE
31-
use fpm_strings, only : lower, split, to_fortran_name, is_fortran_name, remove_characters_in_set, string_t
31+
use fpm_strings, only : lower, split, to_fortran_name, is_fortran_name, remove_characters_in_set, &
32+
string_t, glob
3233
use fpm_filesystem, only : basename, canon_path, which, run
3334
use fpm_environment, only : get_command_arguments_quoted
3435
use fpm_error, only : fpm_stop, error_t
@@ -97,6 +98,7 @@ module fpm_command_line
9798
logical :: example
9899
contains
99100
procedure :: runner_command
101+
procedure :: name_ID
100102
end type
101103

102104
type, extends(fpm_run_settings) :: fpm_test_settings
@@ -1583,5 +1585,27 @@ function runner_command(cmd) result(run_cmd)
15831585
if (len_trim(cmd%runner_args)>0) run_cmd = run_cmd//' '//trim(cmd%runner_args)
15841586
end function runner_command
15851587

1588+
!> Check name in list ID. return 0 if not found
1589+
integer function name_ID(cmd,name)
1590+
class(fpm_run_settings), intent(in) :: cmd
1591+
character(*), intent(in) :: name
1592+
1593+
integer :: j
1594+
1595+
!> Default: not found
1596+
name_ID = 0
1597+
if (.not.allocated(cmd%name)) return
1598+
1599+
do j=1,size(cmd%name)
1600+
1601+
if (glob(trim(name),trim(cmd%name(j)))) then
1602+
name_ID = j
1603+
return
1604+
end if
1605+
1606+
end do
1607+
1608+
end function name_ID
1609+
15861610

15871611
end module fpm_command_line

src/fpm_filesystem.F90

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1011,6 +1011,8 @@ subroutine run(cmd,echo,exitstat,verbose,redirect)
10111011
if (present(redirect)) then
10121012
if(redirect /= '')then
10131013
redirect_str = ">"//redirect//" 2>&1"
1014+
else
1015+
redirect_str = ""
10141016
endif
10151017
else
10161018
if(verbose_local)then

src/fpm_model.f90

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -52,7 +52,7 @@ module fpm_model
5252
FPM_UNIT_SUBMODULE, FPM_UNIT_SUBPROGRAM, FPM_UNIT_CSOURCE, &
5353
FPM_UNIT_CHEADER, FPM_SCOPE_UNKNOWN, FPM_SCOPE_LIB, &
5454
FPM_SCOPE_DEP, FPM_SCOPE_APP, FPM_SCOPE_EXAMPLE, FPM_SCOPE_TEST, &
55-
FPM_UNIT_CPPSOURCE
55+
FPM_UNIT_CPPSOURCE, FPM_SCOPE_NAME
5656

5757
!> Source type unknown
5858
integer, parameter :: FPM_UNIT_UNKNOWN = -1

0 commit comments

Comments
 (0)