Skip to content

Commit f9a55db

Browse files
authored
Fix --example --all (#1021)
2 parents 16a7fbf + 94758f7 commit f9a55db

File tree

9 files changed

+169
-45
lines changed

9 files changed

+169
-45
lines changed

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
@@ -484,7 +484,7 @@ subroutine cmd_run(settings,test)
484484
type(build_target_t), pointer :: exe_target
485485
type(srcfile_t), pointer :: exe_source
486486
integer :: run_scope,firsterror
487-
integer, allocatable :: stat(:)
487+
integer, allocatable :: stat(:),target_ID(:)
488488
character(len=:),allocatable :: line
489489
logical :: toomany
490490

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

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

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

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
@@ -96,6 +97,7 @@ module fpm_command_line
9697
logical :: example
9798
contains
9899
procedure :: runner_command
100+
procedure :: name_ID
99101
end type
100102

101103
type, extends(fpm_run_settings) :: fpm_test_settings
@@ -1541,5 +1543,27 @@ function runner_command(cmd) result(run_cmd)
15411543
if (len_trim(cmd%runner_args)>0) run_cmd = run_cmd//' '//trim(cmd%runner_args)
15421544
end function runner_command
15431545

1546+
!> Check name in list ID. return 0 if not found
1547+
integer function name_ID(cmd,name)
1548+
class(fpm_run_settings), intent(in) :: cmd
1549+
character(*), intent(in) :: name
1550+
1551+
integer :: j
1552+
1553+
!> Default: not found
1554+
name_ID = 0
1555+
if (.not.allocated(cmd%name)) return
1556+
1557+
do j=1,size(cmd%name)
1558+
1559+
if (glob(trim(name),trim(cmd%name(j)))) then
1560+
name_ID = j
1561+
return
1562+
end if
1563+
1564+
end do
1565+
1566+
end function name_ID
1567+
15441568

15451569
end module fpm_command_line

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)