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