Skip to content

Commit 4a97217

Browse files
authored
feat: Improve feature verbosity
2 parents 04a13b6 + c9b0611 commit 4a97217

File tree

5 files changed

+120
-34
lines changed

5 files changed

+120
-34
lines changed

src/fpm.f90

Lines changed: 13 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -86,9 +86,20 @@ subroutine build_model(model, settings, package_config, error)
8686
model%include_tests = settings%build_tests
8787

8888
! Extract the current package configuration request
89-
package = package_config%export_config(target_platform,settings%features,settings%profile,error)
89+
package = package_config%export_config(target_platform,settings%features,settings%profile, &
90+
settings%verbose,error)
9091
if (allocated(error)) return
9192

93+
! Print enabled features/profile in verbose mode
94+
if (settings%verbose) then
95+
if (allocated(settings%features)) then
96+
if (size(settings%features)>0) print *, '+ features: [', string_cat(settings%features,','),']'
97+
end if
98+
if (allocated(settings%profile)) then
99+
print *, '+ profile: ', settings%profile
100+
end if
101+
end if
102+
92103
! Initialize compiler flags using the feature-enabled package configuration
93104
call new_compiler_flags(model, settings, package)
94105

@@ -141,7 +152,7 @@ subroutine build_model(model, settings, package_config, error)
141152

142153
! Adapt it to the current profile/platform
143154
dependency = dependency_config%export_config(target_platform, &
144-
dep%features,error=error)
155+
dep%features,verbose=.false.,error=error)
145156
if (allocated(error)) exit
146157

147158
manifest => dependency

src/fpm/manifest/feature_collection.f90

Lines changed: 1 addition & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1158,14 +1158,9 @@ subroutine merge_into_package(self, package, target, error)
11581158
! Extract the feature configuration for the target platform
11591159
feature = self%extract_for_target(target, error)
11601160
if (allocated(error)) return
1161-
1162-
print *, 'extract for target: flags=',feature%flags
1163-
print *, 'extract for target: link=',feature%link_time_flags
1164-
1161+
11651162
! Merge the extracted feature into the package
11661163
call merge_feature_configs(package, feature, error)
1167-
print *, 'merged for target: flags=',package%flags
1168-
print *, 'merged for target: link=',package%link_time_flags
11691164
if (allocated(error)) return
11701165

11711166
end subroutine merge_into_package

src/fpm/manifest/package.f90

Lines changed: 103 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -480,7 +480,6 @@ subroutine dump_to_toml(self, table, error)
480480
end do
481481
end if
482482

483-
1 format('UNNAMED_',a,'_',i0)
484483
2 format('PROFILE_',i0)
485484

486485
end subroutine dump_to_toml
@@ -560,20 +559,23 @@ subroutine load_from_toml(self, table, error)
560559
end subroutine load_from_toml
561560

562561
!> Export package configuration for a given (OS+compiler) platform
563-
type(package_config_t) function export_config(self, platform, features, profile, error) result(cfg)
564-
565-
!> Instance of the package configuration
562+
type(package_config_t) function export_config(self, platform, features, profile, verbose, error) result(cfg)
563+
564+
!> Instance of the package configuration
566565
class(package_config_t), intent(in), target :: self
567-
566+
568567
!> Target platform
569568
type(platform_config_t), intent(in) :: platform
570-
569+
571570
!> Optional list of features to apply (cannot be used with profile)
572571
type(string_t), optional, intent(in), target :: features(:)
573-
572+
574573
!> Optional profile name to apply (cannot be used with features)
575574
character(len=*), optional, intent(in) :: profile
576-
575+
576+
!> Verbose output flag
577+
logical, optional, intent(in) :: verbose
578+
577579
!> Error handling
578580
type(error_t), allocatable, intent(out) :: error
579581

@@ -604,21 +606,28 @@ type(package_config_t) function export_config(self, platform, features, profile,
604606
nullify(want_features)
605607
endif
606608

607-
apply_features: if (associated(want_features)) then
609+
apply_features: if (associated(want_features)) then
608610
do i=1,size(want_features)
609-
611+
610612
! Find feature
611613
idx = self%find_feature(want_features(i)%s)
612-
if (idx<=0) then
614+
if (idx<=0) then
613615
call fatal_error(error, "Cannot find feature "//want_features(i)%s//&
614616
" in package "//self%name)
615617
return
616618
end if
617-
619+
620+
! Print feature collection info if verbose
621+
if (present(verbose)) then
622+
if (verbose) then
623+
call print_feature_collection(self%features(idx), platform)
624+
end if
625+
end if
626+
618627
! Add it to the current configuration
619628
call self%features(idx)%merge_into_package(cfg, platform, error)
620629
if (allocated(error)) return
621-
630+
622631
end do
623632
end if apply_features
624633

@@ -752,20 +761,96 @@ subroutine validate_profiles(self, error)
752761
end subroutine validate_profiles
753762

754763
!> Check if there is a CPP preprocessor configuration
755-
elemental logical function has_cpp(self)
764+
elemental logical function has_cpp(self)
756765
class(package_config_t), intent(in) :: self
757-
766+
758767
integer :: i
759-
768+
760769
has_cpp = self%feature_config_t%has_cpp()
761770
if (has_cpp) return
762771
if (.not.allocated(self%features)) return
763-
772+
764773
do i=1,size(self%features)
765774
has_cpp = self%features(i)%has_cpp()
766775
if (has_cpp) return
767776
end do
768-
777+
769778
end function has_cpp
770779

780+
!> Print feature collection information in verbose mode
781+
subroutine print_feature_collection(collection, platform)
782+
use, intrinsic :: iso_fortran_env, only: stdout => output_unit
783+
use fpm_compiler, only: compiler_name
784+
use fpm_environment, only: os_name
785+
use fpm_strings, only: string_cat
786+
type(feature_collection_t), intent(in) :: collection
787+
type(platform_config_t), intent(in) :: platform
788+
789+
type(feature_config_t) :: extracted
790+
type(error_t), allocatable :: error_tmp
791+
integer :: i, j, n_macros
792+
793+
! Extract the feature configuration for the target platform
794+
extracted = collection%extract_for_target(platform, error_tmp)
795+
if (allocated(error_tmp)) return
796+
797+
! Print header with feature name
798+
if (allocated(extracted%name)) then
799+
print *, '+ feature collection: ', trim(extracted%name)
800+
end if
801+
802+
! Print platform information
803+
print *, '+ platform: ', platform%compiler_name(), ' on ', platform%os_name()
804+
805+
! Print flags
806+
if (allocated(extracted%flags)) then
807+
print *, '+ flags: ', trim(extracted%flags)
808+
end if
809+
if (allocated(extracted%c_flags)) then
810+
print *, '+ c-flags: ', trim(extracted%c_flags)
811+
end if
812+
if (allocated(extracted%cxx_flags)) then
813+
print *, '+ cxx-flags: ', trim(extracted%cxx_flags)
814+
end if
815+
if (allocated(extracted%link_time_flags)) then
816+
print *, '+ link-flags: ', trim(extracted%link_time_flags)
817+
end if
818+
819+
! Print preprocessor macros
820+
if (allocated(extracted%preprocess)) then
821+
n_macros = 0
822+
do i = 1, size(extracted%preprocess)
823+
if (allocated(extracted%preprocess(i)%macros)) then
824+
n_macros = n_macros + size(extracted%preprocess(i)%macros)
825+
end if
826+
end do
827+
828+
if (n_macros > 0) then
829+
print *, '+ cpp-macros: yes (', n_macros, ' defined)'
830+
do i = 1, size(extracted%preprocess)
831+
if (allocated(extracted%preprocess(i)%macros)) then
832+
do j = 1, size(extracted%preprocess(i)%macros)
833+
print *, '+ - ', trim(extracted%preprocess(i)%macros(j)%s)
834+
end do
835+
end if
836+
end do
837+
else
838+
print *, '+ cpp-macros: no'
839+
end if
840+
else
841+
print *, '+ cpp-macros: no'
842+
end if
843+
844+
! Print description if available
845+
if (allocated(extracted%description)) then
846+
print *, '+ description: ', trim(extracted%description)
847+
end if
848+
849+
! Print number of variants in collection
850+
if (allocated(collection%variants)) then
851+
print *, '+ variants: ', size(collection%variants)
852+
end if
853+
854+
end subroutine print_feature_collection
855+
771856
end module fpm_manifest_package

src/fpm/manifest/platform.f90

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -257,7 +257,6 @@ logical function platform_is_suitable(self, target) result(ok)
257257
! Check that both platforms are valid
258258
if (.not. self%is_valid() .or. .not. target%is_valid()) then
259259
ok = .false.
260-
print *, 'compare platform ',self%name(),' with target ',target%name(),': ok=',ok
261260
return
262261
end if
263262

@@ -267,8 +266,6 @@ logical function platform_is_suitable(self, target) result(ok)
267266
! Basic matching
268267
ok = compiler_ok .and. os_ok
269268

270-
if (.not.ok) print *, 'compare platform ',self%name(),' with target ',target%name(),': ok=',ok
271-
272269
if (.not. ok) return
273270

274271
! Additional validation: Intel compilers must have compatible OS
@@ -278,8 +275,6 @@ logical function platform_is_suitable(self, target) result(ok)
278275
compiler_os_compatible(target%compiler, target%os_type)
279276
end if
280277

281-
print *, 'compare platform ',self%name(),' with target ',target%name(),': ok=',ok
282-
283278
end function platform_is_suitable
284279

285280
!> Check if a platform configuration is valid (no unknowns, compatible compiler+OS)

test/fpm_test/test_features.f90

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1157,7 +1157,7 @@ subroutine test_dependency_feature_propagation(error)
11571157

11581158
! Test export_config with these features (mimics line 132-133 in fpm.f90)
11591159
target_platform = platform_config_t(id_gcc, OS_LINUX)
1160-
exported_config = dependency_config%export_config(target_platform, test_features, error=error)
1160+
exported_config = dependency_config%export_config(target_platform, test_features, verbose=.false., error=error)
11611161
if (allocated(error)) return
11621162

11631163
! Verify that debug feature flags were applied
@@ -1524,7 +1524,7 @@ subroutine test_feature_compiler_flags_integration(error)
15241524
settings%profile = "development" ! This should activate debug features
15251525

15261526
! Extract the current package configuration request
1527-
package = package_config%export_config(target_platform, profile=settings%profile, error=error)
1527+
package = package_config%export_config(target_platform, profile=settings%profile, verbose=.false., error=error)
15281528
if (allocated(error)) return
15291529

15301530
! Set up model with mock compiler
@@ -1558,7 +1558,7 @@ subroutine test_feature_compiler_flags_integration(error)
15581558
settings%profile = "production" ! This should activate release features
15591559

15601560
! Extract the new package configuration request
1561-
package = package_config%export_config(target_platform, profile=settings%profile, error=error)
1561+
package = package_config%export_config(target_platform, profile=settings%profile, verbose=.false., error=error)
15621562
if (allocated(error)) return
15631563

15641564
! Reset flags and test production profile

0 commit comments

Comments
 (0)