@@ -45,7 +45,7 @@ module fpm_targets
45
45
FPM_TARGET_SHARED, FPM_TARGET_NAME
46
46
public build_target_t, build_target_ptr
47
47
public targets_from_sources, resolve_module_dependencies
48
- public add_target, add_dependency, get_library_dirs
48
+ public add_target, new_target, add_dependency, get_library_dirs
49
49
public filter_library_targets, filter_executable_targets, filter_modules
50
50
51
51
@@ -148,6 +148,11 @@ module fpm_targets
148
148
149
149
end type build_target_t
150
150
151
+ interface add_target
152
+ module procedure add_new_target
153
+ module procedure add_old_target
154
+ module procedure add_old_targets
155
+ end interface
151
156
152
157
contains
153
158
@@ -269,8 +274,8 @@ subroutine targets_from_sources(targets,model,prune,library,error)
269
274
! all sources to be distributable
270
275
should_prune = prune
271
276
if (present (library)) should_prune = should_prune .and. library% monolithic()
272
-
273
- call prune_build_targets(targets,model% package_name ,should_prune)
277
+
278
+ call prune_build_targets(targets,model% packages( 1 ) ,should_prune)
274
279
275
280
call resolve_target_linking(targets,model,library,error)
276
281
if (allocated (error)) return
@@ -345,17 +350,20 @@ subroutine build_target_list(targets,model,library)
345
350
type = FPM_TARGET_ARCHIVE,output_name = lib_name)
346
351
347
352
elseif (shared_lib .or. static_lib) then
348
- ! Package libraries go to the same path as the `.mod` files (consistent linking directories)
353
+
354
+ ! Individual package libraries are built.
355
+ ! Create as many targets as the packages in the dependency tree
349
356
do j= 1 ,size (model% packages)
350
357
351
358
lib_name = library_filename(model% packages(j)% name,shared_lib,.false. ,get_os_type())
352
359
353
360
call add_target(targets,package= model% packages(j)% name, &
354
- type = merge (FPM_TARGET_SHARED,FPM_TARGET_ARCHIVE,shared_lib),output_name = lib_name)
361
+ type= merge (FPM_TARGET_SHARED,FPM_TARGET_ARCHIVE,shared_lib), &
362
+ output_name= lib_name)
355
363
end do
356
364
357
365
endif
358
-
366
+
359
367
do j= 1 ,size (model% packages)
360
368
361
369
associate(sources= >model% packages(j)% sources)
@@ -553,9 +561,43 @@ subroutine collect_exe_link_dependencies(targets)
553
561
554
562
end subroutine collect_exe_link_dependencies
555
563
564
+ ! > Allocate a new target
565
+ type (build_target_ptr) function new_target(package, type, output_name, source, link_libraries, &
566
+ & features, preprocess, version, output_dir)
567
+ character (* ), intent (in ) :: package
568
+ integer , intent (in ) :: type
569
+ character (* ), intent (in ) :: output_name
570
+ type (srcfile_t), intent (in ), optional :: source
571
+ type (string_t), intent (in ), optional :: link_libraries(:)
572
+ type (fortran_features_t), intent (in ), optional :: features
573
+ type (preprocess_config_t), intent (in ), optional :: preprocess
574
+ character (* ), intent (in ), optional :: version
575
+ character (* ), intent (in ), optional :: output_dir
576
+
577
+ allocate (new_target% ptr)
578
+
579
+ associate(target = >new_target% ptr)
580
+
581
+ target % target_type = type
582
+ target % output_name = output_name
583
+ target % package_name = package
584
+ if (present (source)) target % source = source
585
+ if (present (link_libraries)) target % link_libraries = link_libraries
586
+ if (present (features)) target % features = features
587
+ if (present (preprocess)) then
588
+ if (allocated (preprocess% macros)) target % macros = preprocess% macros
589
+ endif
590
+ if (present (version)) target % version = version
591
+ allocate (target % dependencies(0 ))
592
+
593
+ call target % set_output_dir(output_dir)
594
+
595
+ endassociate
596
+
597
+ end function new_target
556
598
557
599
! > Allocate a new target and append to target list
558
- subroutine add_target (targets , package , type , output_name , source , link_libraries , &
600
+ subroutine add_new_target (targets , package , type , output_name , source , link_libraries , &
559
601
& features , preprocess , version , output_dir )
560
602
type (build_target_ptr), allocatable , intent (inout ) :: targets(:)
561
603
character (* ), intent (in ) :: package
@@ -568,45 +610,55 @@ subroutine add_target(targets, package, type, output_name, source, link_librarie
568
610
character (* ), intent (in ), optional :: version
569
611
character (* ), intent (in ), optional :: output_dir
570
612
571
- integer :: i
572
- type (build_target_t), pointer :: new_target
613
+ type (build_target_ptr) :: added
573
614
574
615
if (.not. allocated (targets)) allocate (targets(0 ))
616
+
617
+ ! Create new target
618
+ added = new_target(package,type,output_name,source,link_libraries,features,preprocess,&
619
+ version,output_dir)
620
+
621
+ call add_old_target(targets, added)
622
+
623
+ end subroutine add_new_target
575
624
625
+ subroutine add_old_targets (targets , add_targets )
626
+ type (build_target_ptr), allocatable , intent (inout ) :: targets(:)
627
+ type (build_target_ptr), intent (in ) :: add_targets(:)
628
+
629
+ integer :: i,j
630
+
631
+ if (.not. allocated (targets)) allocate (targets(0 ))
632
+
576
633
! Check for duplicate outputs
577
- do i= 1 ,size (targets)
634
+ do j= 1 ,size (add_targets)
635
+ associate(added= >add_targets(j)% ptr)
578
636
579
- if (targets(i) % ptr % output_name == output_name) then
637
+ do i = 1 , size (targets)
580
638
581
- write (* ,* ) ' Error while building target list: duplicate output object "' ,&
582
- output_name,' "'
583
- if (present (source)) write (* ,* ) ' Source file: "' ,source% file_name,' "'
584
- call fpm_stop(1 ,' ' )
639
+ if (targets(i)% ptr% output_name == added% output_name) then
585
640
586
- end if
641
+ write (* ,* ) ' Error while building target list: duplicate output object "' ,&
642
+ added% output_name,' "'
643
+ if (allocated (added% source)) write (* ,* ) ' Source file: "' ,added% source% file_name,' "'
644
+ call fpm_stop(1 ,' ' )
587
645
588
- end do
646
+ end if
589
647
590
- allocate (new_target)
591
- new_target% target_type = type
592
- new_target% output_name = output_name
593
- new_target% package_name = package
594
- if (present (source)) new_target% source = source
595
- if (present (link_libraries)) new_target% link_libraries = link_libraries
596
- if (present (features)) new_target% features = features
597
- if (present (preprocess)) then
598
- if (allocated (preprocess% macros)) new_target% macros = preprocess% macros
599
- endif
600
- if (present (version)) new_target% version = version
601
- allocate (new_target% dependencies(0 ))
602
-
603
- call new_target% set_output_dir(output_dir)
648
+ end do
649
+
650
+ endassociate
651
+ end do
604
652
653
+ targets = [targets, add_targets ]
605
654
606
- targets = [targets, build_target_ptr(new_target)]
607
-
608
- end subroutine add_target
655
+ end subroutine add_old_targets
609
656
657
+ subroutine add_old_target (targets , add_target )
658
+ type (build_target_ptr), allocatable , intent (inout ) :: targets(:)
659
+ type (build_target_ptr), intent (in ) :: add_target
660
+ call add_old_targets(targets, [add_target])
661
+ end subroutine add_old_target
610
662
611
663
! > Add pointer to dependeny in target%dependencies
612
664
subroutine add_dependency (target , dependency )
@@ -740,8 +792,8 @@ subroutine prune_build_targets(targets, root_package, prune_unused_objects)
740
792
! > Build target list to prune
741
793
type (build_target_ptr), intent (inout ), allocatable :: targets(:)
742
794
743
- ! > Name of root package
744
- character ( * ), intent (in ) :: root_package
795
+ ! > Root package
796
+ type (package_t ), intent (in ) :: root_package
745
797
746
798
! > Whether unused objects should be pruned
747
799
logical , intent (in ) :: prune_unused_objects
@@ -784,7 +836,7 @@ subroutine prune_build_targets(targets, root_package, prune_unused_objects)
784
836
785
837
do i= 1 ,size (targets)
786
838
787
- if (targets(i)% ptr% package_name == root_package .and. &
839
+ if (targets(i)% ptr% package_name == root_package% name .and. &
788
840
all (targets(i)% ptr% target_type /= [FPM_TARGET_ARCHIVE,FPM_TARGET_SHARED])) then
789
841
790
842
call collect_used_modules(targets(i)% ptr)
@@ -848,10 +900,11 @@ subroutine prune_build_targets(targets, root_package, prune_unused_objects)
848
900
849
901
end if
850
902
851
- ! (If there aren't any executables then we only prune modules from dependencies)
852
- if (nexec < 1 .and. target % package_name == root_package) then
853
- exclude_target(i) = .false.
854
- target % skip = .false.
903
+ ! (If there aren't any executables then we only prune modules from dependencies,
904
+ ! unless the root package is also empty)
905
+ if (nexec < 1 .and. target % package_name == root_package% name) then
906
+ exclude_target(i) = .not. root_package% has_library()
907
+ target % skip = exclude_target(i)
855
908
end if
856
909
857
910
end associate
@@ -964,7 +1017,7 @@ subroutine resolve_target_linking(targets, model, library, error)
964
1017
965
1018
integer :: i,j
966
1019
logical :: shared,static,monolithic,has_self_lib
967
- integer , allocatable :: package_deps(:)
1020
+ integer , allocatable :: package_deps(:),dep_target_ID(:)
968
1021
character (:), allocatable :: global_link_flags, local_link_flags
969
1022
character (:), allocatable :: global_include_flags, shared_lib_paths
970
1023
@@ -1027,16 +1080,14 @@ subroutine resolve_target_linking(targets, model, library, error)
1027
1080
1028
1081
call target % set_output_dir(get_output_dir(model% build_prefix, target % compile_flags))
1029
1082
1030
- ! Check shared build
1031
- if (target % target_type== FPM_TARGET_SHARED) shared = .true.
1032
-
1033
1083
end associate
1034
1084
1035
1085
end do
1036
1086
1037
1087
call add_include_build_dirs(model, targets)
1038
1088
call add_library_link_dirs(model, targets, shared_lib_paths)
1039
-
1089
+ call library_targets_to_deps(model, targets, dep_target_ID)
1090
+
1040
1091
do i= 1 ,size (targets)
1041
1092
1042
1093
associate(target = > targets(i)% ptr)
@@ -1074,7 +1125,8 @@ subroutine resolve_target_linking(targets, model, library, error)
1074
1125
! Now that they're available, add these dependencies to the targets
1075
1126
if (size (package_deps)>0 ) then
1076
1127
do j= 1 ,size (package_deps)
1077
- call add_dependency(target , targets(package_deps(j))% ptr)
1128
+ if (dep_target_ID(package_deps(j))<= 0 ) cycle
1129
+ call add_dependency(target , targets(dep_target_ID(package_deps(j)))% ptr)
1078
1130
end do
1079
1131
end if
1080
1132
@@ -1388,5 +1440,34 @@ subroutine set_output_dir(self, output_dir)
1388
1440
1389
1441
end subroutine set_output_dir
1390
1442
1443
+ ! > Build a lookup table mapping each package dependency to its corresponding
1444
+ ! > shared or archive build target in the targets list.
1445
+ ! >
1446
+ ! > This mapping is essential when model%deps%dep(i) indices do not match
1447
+ ! > the pruned or reordered targets(:) array.
1448
+ subroutine library_targets_to_deps (model , targets , target_ID )
1449
+ class(fpm_model_t), intent (in ) :: model
1450
+ type (build_target_ptr), intent (in ) :: targets(:)
1451
+
1452
+ ! > For each package (by dependency index), gives the index of the corresponding target
1453
+ integer , allocatable , intent (out ) :: target_ID(:)
1454
+
1455
+ integer :: it, ip, n
1456
+
1457
+ n = size (model% deps% dep)
1458
+ allocate (target_ID(n), source= 0 )
1459
+
1460
+ do it = 1 , size (targets)
1461
+ associate(target = > targets(it)% ptr)
1462
+ ! Only shared libraries and archives are mapped
1463
+ if (all (target % target_type /= [FPM_TARGET_ARCHIVE, FPM_TARGET_SHARED])) cycle
1464
+
1465
+ ! Get the dependency graph index of this package
1466
+ ip = model% deps% find(target % package_name)
1467
+ if (ip > 0 ) target_ID(ip) = it
1468
+ end associate
1469
+ end do
1470
+
1471
+ end subroutine library_targets_to_deps
1391
1472
1392
1473
end module fpm_targets
0 commit comments