@@ -484,7 +484,7 @@ subroutine cmd_run(settings,test)
484
484
type (build_target_t), pointer :: exe_target
485
485
type (srcfile_t), pointer :: exe_source
486
486
integer :: run_scope,firsterror
487
- integer , allocatable :: stat(:)
487
+ integer , allocatable :: stat(:),target_ID(:)
488
488
character (len= :),allocatable :: line
489
489
logical :: toomany
490
490
@@ -512,48 +512,31 @@ subroutine cmd_run(settings,test)
512
512
! Enumerate executable targets to run
513
513
col_width = - 1
514
514
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)
518
517
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
+
523
520
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
+
557
540
! Check if any apps/tests were found
558
541
if (col_width < 0 ) then
559
542
if (test) then
@@ -563,8 +546,6 @@ subroutine cmd_run(settings,test)
563
546
end if
564
547
end if
565
548
566
-
567
-
568
549
! Check all names are valid
569
550
! or no name and found more than one file
570
551
toomany= size (settings% name)==0 .and. size (executables)>1
@@ -735,4 +716,86 @@ subroutine cmd_clean(settings)
735
716
end if
736
717
end subroutine cmd_clean
737
718
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
+
738
801
end module fpm
0 commit comments